PIPS
outlining.c
Go to the documentation of this file.
1 /*
2 
3  $Id: outlining.c 23495 2018-10-24 09:19:47Z coelho $
4 
5  Copyright 1989-2016 MINES ParisTech
6 
7  This file is part of PIPS.
8 
9  PIPS is free software: you can redistribute it and/or modify it
10  under the terms of the GNU General Public License as published by
11  the Free Software Foundation, either version 3 of the License, or
12  any later version.
13 
14  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
15  WARRANTY; without even the implied warranty of MERCHANTABILITY or
16  FITNESS FOR A PARTICULAR PURPOSE.
17 
18  See the GNU General Public License for more details.
19 
20  You should have received a copy of the GNU General Public License
21  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
22 
23 */
24 /**
25  * @file outlining.c
26  * @brief add outlining support to pips, with two flavors
27  *
28  * @author Serge Guelton <serge.guelton@enst-bretagne.fr>
29  * @date 2009-01-07
30  */
31 #ifdef HAVE_CONFIG_H
32  #include "pips_config.h"
33 #endif
34 #include <stdio.h>
35 #include <stdlib.h>
36 #include <string.h>
37 #include "genC.h"
38 #include "linear.h"
39 #include "ri.h"
40 #include "effects.h"
41 #include "ri-util.h"
42 #include "prettyprint.h"
43 #include "effects-util.h"
44 #include "text.h"
45 #include "pipsdbm.h"
46 #include "syntheses.h" // Where outlining.c should be stored...
47 #include "pipsmake.h"
48 #include "resources.h"
49 #include "properties.h"
50 #include "misc.h"
51 #include "control.h"
52 #include "callgraph.h"
53 #include "effects-generic.h"
54 #include "effects-convex.h"
55 #include "preprocessor.h"
56 #include "expressions.h"
57 #include "text-util.h"
58 #include "parser_private.h"
59 #include "accel-util.h"
60 #include "transformations.h"
61 /**
62  * @name outlining
63  * @{ */
64 
66 {
67  return strdup(" Declared by Pass Outlining\n");
68 }
69 
71 {
72  return strdup(" Declared as a patch variable by Pass Outlining\n");
73 }
74 
75 #define STAT_ORDER "PRETTYPRINT_STATEMENT_NUMBER"
76 
78  if(statement_loop_p(st)) {
79  loop l = statement_loop(st);
80  list locals = loop_locals(l);
81 
82  /* loop_locals is sometimes too big,
83  * mainly due to the way gpu_ify is done ...
84  */
87  set_add_element(re0,re0,loop_index(l));
88  set_union(re0,re0,re1);
89  set_free(re1);
90 
91  /* validate everything */
92  FOREACH(ENTITY,el,locals) {
93  if(set_belong_p(re0,el))
94  set_add_element(s,s,el);
95  }
96  set_free(re0);
97 
98  /* remove instructions for later processing */
101  }
102 }
103 
104 static
106  set locals = set_make(set_pointer);
108  return locals;
109 }
110 
111 /* try hard to reproduce in / out regions with only loop_locals
112  * it is time to move to regions ... are they stable enough ?
113  */
114 static
119  set_difference(locals,locals,re);
120  set_free(re);
122  return locals;
123 }
124 
125 static bool skip_values(void *v) {
126  return !INSTANCE_OF(value,(gen_chunkp)v);
127 }
128 
131  !member_entity_p(e);
132 }
133 
134 
135 static
137 {
139  FOREACH(ENTITY,e,*l)
140  {
141  if(!storage_rom_p(entity_storage(e))) { //<< to avoid gathering useless variables, unsure of the validity
143  set_del_element(e_ref,e_ref,e);
144  set_union(params,params,e_ref);
145  set_free(e_ref);
146  }
147  }
148 
150  set_assign_list(base,*l);
152 
155 
157  gen_free_list(*l);
158 
159  *l=gen_nconc(l_params,l_base);
160 }
161 
162 struct cpv {
164  bool rm;
165 };
166 
167 
168 static
170 {
172  if(set_belong_p(s,p->e)){
173  p->rm=true;
174  gen_recurse_stop(0);
175  }
176  set_free(s);
177 }
178 static
180 {
181  return !has_entity_with_same_name(p->e,loop_locals(l));
182 }
183 
184 static
186 {
187  set s = get_private_entities(stat);
188 
189  list l =NIL;
190  SET_FOREACH(entity,e,s) {
191  struct cpv p = { .e=e, .rm=false };
195  0);
196  if(!p.rm)
197  l=CONS(ENTITY,e,l);
198  }
199  set_free(s);
200 
201  return l;
202 }
203 
204 typedef struct {
206  entity new;
207  size_t nb_dims;
208 } ocontext_t;
210 {
211  if(same_entity_p(ctxt->old,reference_variable(r)))
212  {
213  size_t nb_dims = ctxt->nb_dims;
215  while (nb_dims--) POP(indices);
218  unnormalize_expression(parent);
219  if(basic_pointer_p(entity_basic(ctxt->new))) /*sg:may cause issues if basic_pointer_p(old) ? */
220  {
221  pips_assert("parent exist",parent);
222  //free_syntax(expression_syntax(parent)); /* sg a small leak is better than a crash :) */
223  if(!ENDP(indices))
224  expression_syntax(parent)=
228  indices)
229  );
230  else
231  expression_syntax(parent)=
234  );
235 
236  }
237  else {
238  reference_variable(r)=ctxt->new;
241  }
242  }
243 }
244 
245 static void outliner_smart_replacment(statement in, entity old, entity new,size_t nb_dims)
246 {
247  ocontext_t ctxt = { old,new,nb_dims };
249 }
250 
252 {
253  list referenced_entities = NIL;
254  set sreferenced_entities = set_make(set_pointer);
255 
256  FOREACH(STATEMENT, s, statements)
257  {
258  /* we don't want initial values of outer entities */
260  /* gather local initial values skipped by the previous call*/
262  FOREACH(ENTITY,e,decl) {
264  set_union(tmp,tmp,se);
265  set_free(se);
267  set_union(tmp,tmp,se);
268  set_free(se);
269  }
270 
271  ifdebug(7) {
272  pips_debug(7,"Statement :");
273  print_statement(s);
274  pips_debug(7,"referenced entities :");
276  fprintf(stderr,"\n");
277  }
278 
279  set_union(sreferenced_entities,tmp,sreferenced_entities);
280  set_free(tmp);
281  }
282  /* set to list */
283  referenced_entities=set_to_list(sreferenced_entities);
284  set_free(sreferenced_entities);
285  return referenced_entities;
286 }
287 /**
288  * purge the list of referenced entities by replacing calls to a[i][j] where i is a constant in statements
289  * outlined_statements by a call to a single (new) variable
290  */
291 static hash_table outliner_smart_references_computation(list outlined_statements,entity new_module)
292 {
293  list referenced_entities = outliner_statements_referenced_entities(outlined_statements);
294 
295  /* this will hold new referenced_entities list */
297  /* first check candidates, that is array entities accessed by a constant index */
298  FOREACH(ENTITY,e,referenced_entities)
299  {
300  FOREACH(STATEMENT,st,outlined_statements)
301  {
302  list regions = load_rw_effects_list(st);
303  list the_constant_indices = NIL;
305  FOREACH(REGION,reg,regions)
306  {
309  {
310  list constant_indices = NIL;
311  Psysteme sc = region_system(reg);
313  {
314  Variable phi = expression_to_entity(index);
315  expression index_value = expression_undefined;
316  /* we are looking for constant index, so only check equalities */
317  for(Pcontrainte iter = sc_egalites(sc);iter;iter=contrainte_succ(iter))
318  {
319  Pvecteur cvect = contrainte_vecteur(iter);
320  Value phi_coeff = vect_coeff(phi,cvect);
321  if(phi_coeff != VALUE_ZERO )
322  {
323  pips_assert("phi coef should be one",phi_coeff == VALUE_ONE);
324  Pvecteur lhs_vect = vect_del_var(cvect,phi);
325  vect_chg_sgn(lhs_vect);
326  pips_assert("phi coef should be mentioned only once",expression_undefined_p(index_value));
327  index_value = VECTEUR_NUL_P(lhs_vect) ? int_to_expression(0) : Pvecteur_to_expression(lhs_vect);
328  vect_rm(lhs_vect);
329  }
330  }
331  if(!expression_undefined_p(index_value))
332  {
333  /* it's ok, we can keep on finding constant indices */
334  constant_indices=CONS(EXPRESSION,index_value,constant_indices);
335  }
336  else break;
337  }
338  constant_indices=gen_nreverse(constant_indices);
339  /* check for clashes */
340  if(!ENDP(the_constant_indices) && ! gen_equals(constant_indices,the_constant_indices,(gen_eq_func_t)same_expression_p))
341  {
342  /* abort there , we could be smarter */
343  gen_full_free_list(the_constant_indices);
344  gen_full_free_list(constant_indices);
345  the_constant_indices=constant_indices=NIL;
346  break;
347  }
348  else if( ENDP(the_constant_indices) )
349  {
350  the_constant_indices=constant_indices;
351  mode=region_action(reg);
352  }
353  else if( action_read_p(mode) && action_write_p(region_action(reg)))
354  {
355  mode =region_action(reg);
356  }
357  }
358  }
359  /* we have gathered a sub array of e that is constant and we know its mode
360  * get ready for substitution in the statement */
361  if(!ENDP(the_constant_indices))
362  {
363  size_t nb_constant_indices = gen_length(the_constant_indices);
364  list entity_dimensions = variable_dimensions(type_variable(entity_type(e)));
365  size_t nb_dimensions = gen_length(entity_dimensions);
366 
367  /* compute new dimensions */
368  list new_dimensions = NIL;
369  size_t count_dims = 0;
370  for(list iter = entity_dimensions;!ENDP(iter);POP(iter))
371  {
372  ++count_dims;
373  if(count_dims==nb_constant_indices) { new_dimensions=gen_full_copy_list(CDR(iter));break; }
374  }
375 
376 
377  basic new_basic;
378  if(action_read_p(mode)&&nb_constant_indices==nb_dimensions)
379  new_basic=copy_basic(entity_basic(e));
380  else
381  {
382  type new_type = make_type_variable(
385  new_dimensions,
387  )
388  );
389  new_basic=make_basic_pointer(new_type);
390  }
391 
392  entity new_entity;
393  if(action_read_p(mode)&&nb_constant_indices==nb_dimensions)
394  {
396  entity_user_name(e),
397  new_module,
398  new_basic,
399  new_dimensions);
400  }
401  else
402  {
404  entity_user_name(e),
405  new_module,
406  new_basic);
407  }
408  outliner_smart_replacment(st,e,new_entity,nb_constant_indices);
409  expression effective_parameter = reference_to_expression(make_reference(e,the_constant_indices));
410  if(!(action_read_p(mode)&&nb_constant_indices==nb_dimensions))
411  effective_parameter=MakeUnaryCall(entity_intrinsic(ADDRESS_OF_OPERATOR_NAME),effective_parameter);
412  hash_put(entity_to_init,new_entity,effective_parameter);
413  }
414  }
415  }
416  gen_free_list(referenced_entities);
417 
418  return entity_to_init;
419 }
421 {
422  list sd = statements_to_declarations(statements);
423  list localized = NIL;
424  FOREACH(STATEMENT, s, statements)
425  {
426  /* We want to declare private variables **that are never used else where** as locals, but it may not
427  be valid */
428  list private_ents = private_variables(s);
430  FOREACH(ENTITY,e,private_ents)
431  {
433  if(formal_parameter_p(e) ||
434  (!get_bool_property("OUTLINE_ALLOW_GLOBALS") && top_level_entity_p(e) )) { // otherwise bad interaction with formal parameter pretty printing
435  localized=CONS(ENTITY,e,localized); // this is to make sure that the original `e' is removed from the referenced entities too
437  entity_user_name(e),
438  module,
440  );
441  replace_entity(s,e,ep);
442  e=ep;
443  }
445  localized=CONS(ENTITY,e,localized);
446  }
447  }
448  gen_free_list(private_ents);
449  }
450  gen_free_list(sd);
451  return localized;
452 }
453 static void outliner_extract_loop_bound(statement sloop, hash_table entity_to_effective_parameter)
454 {
455  loop l =statement_loop(sloop);
456  range r = loop_range(l);
457  expression upper = range_upper(r);
458  if(!expression_scalar_p(upper))
459  {
460  basic b = basic_of_expression(upper);
463  hash_put(entity_to_effective_parameter,holder,
465  range_upper(r)=
467  }
468 }
476  make_call(
481  ),
482  NIL)
483  )
484  );
486  }
487  }
488 }
492 }
493 
494 static void convert_pointer_to_array(entity e,entity re, expression x, list statements) {
495  type t =entity_type(e);
498  type_variable(t)
499  )
500  );
503  type_variable(t)
504  )
505  )=type_undefined;
506  free_type(t);
508  FOREACH(STATEMENT,s,statements) {
511  NULL);
513  }
514 
515  /* crado */
516  syntax syn = expression_syntax(x);
519  make_call(
524  ),
525  NIL)
526  )
527  );
529 }
530 
532  list tentities = gen_copy_seq(*entities);
533  for(list iter=tentities;!ENDP(iter);POP(iter)) {
534  entity e0 = ENTITY(CAR(iter));
535  FOREACH(ENTITY,e1,CDR(iter)) {
536  if( !same_entity_p(e0,e1) &&
537  same_entity_lname_p(e0,e1)) {
539  break;
540  }
541  }
542  }
543  gen_free_list(tentities);
544 }
545 
546 hash_table outliner_init(entity new_fun, list statements_to_outline)
547 {
548  /* try to be smart concerning array references */
549  if(get_bool_property("OUTLINE_SMART_REFERENCE_COMPUTATION"))
550  return outliner_smart_references_computation(statements_to_outline, new_fun);
551  else
552  return hash_table_make(hash_pointer,1);
553 }
554 
555 list outliner_scan(entity new_fun, list statements_to_outline, statement new_body)
556 {
557  /* Retrieve referenced entities */
558  list referenced_entities = outliner_statements_referenced_entities(statements_to_outline);
559 
560  ifdebug(5) {
561  pips_debug(5,"Referenced entities :\n");
562  print_entities(referenced_entities);
563  }
564 
565  /* Retrieve declared entities */
567  list localized = statements_localize_declarations(statements_to_outline,new_fun,new_body);
569  list declared_entities = statements_to_declarations(statements_to_outline);
570  FOREACH(ENTITY,e,declared_entities)
572  declared_entities=gen_nconc(declared_entities,localized);
573 
574  /* get the relative complements and create the parameter list*/
575  gen_list_and_not(&referenced_entities,declared_entities);
576  gen_free_list(declared_entities);
577 
578 
579  /* purge the functions from the parameter list, we assume they are declared externally
580  * also purge the formal parameters from other modules, gathered by get_referenced_entities but wrong here
581  */
582  list tmp = gen_copy_seq(referenced_entities);
583  FOREACH(ENTITY,e,referenced_entities)
584  {
585  //basic b = entity_basic(e);
586  /* function should be added to compilation unit */
587  if(entity_function_p(e))
588  {
589  ;//AddEntityToModuleCompilationUnit(e,get_current_module_entity());
590  if(!fortran_module_p(new_fun)) /* fortran function results must be declared in the new function */
591  gen_remove_once(&referenced_entities,e);
592  }
593  }
594  gen_free_list(tmp);
595 
596 
597 
598  /* remove global variables if needed */
599  if(get_bool_property("OUTLINE_ALLOW_GLOBALS"))
600  {
602  entity cu = module_name_to_entity(cu_name);
603  list cu_decls = entity_declarations(cu);
604 
605  list tmp_list=NIL;
606 
607  FOREACH(ENTITY,e,referenced_entities)
608  {
609  if( !top_level_entity_p(e) && gen_chunk_undefined_p(gen_find_eq(e,cu_decls) ) )
610  tmp_list=CONS(ENTITY,e,tmp_list);
611  else if (gen_chunk_undefined_p(gen_find_eq(e,cu_decls)))
612  {
613  AddLocalEntityToDeclarations(e,new_fun,new_body);
614  }
615  }
616  gen_free_list(referenced_entities);
617  referenced_entities=tmp_list;
618  }
619 
620  /* sort list, and put parameters first */
621  sort_entities_with_dep(&referenced_entities);
622 
623 
624  /* in some rare case, we can have too functions with the same local name */
625  outline_remove_duplicates(&referenced_entities);
626  return referenced_entities;
627 }
628 /* create a new type from given type, eventually renaming unnamed structures inside
629  * all new entities generated in the process are added to cu*/
630 static
632  type tp = t;
633  variable tv = type_variable(tp);
634  basic b = variable_basic(tv);
635  if(basic_derived_p(b)) {
636  entity at = basic_derived(b);
637  bool is_struct = false;
638  if( (is_struct=strncmp(entity_user_name(at),DUMMY_STRUCT_PREFIX,sizeof(DUMMY_STRUCT_PREFIX)-1)==0)
639  || strncmp(entity_user_name(at),DUMMY_UNION_PREFIX, sizeof(DUMMY_UNION_PREFIX)-1)==0 )
640  {
641  /* create a new named type */
642  int index = 0;
643  char* name = strdup("");;
644  do {
645  free(name);
646  asprintf(&name, "%s" MODULE_SEP_STRING "%cstruct_%d", entity_local_name(cu), is_struct?STRUCT_PREFIX_CHAR:UNION_PREFIX_CHAR,index++);
648 
649  FOREACH(ENTITY,filed,is_struct?type_struct(entity_type(at)):type_union(entity_type(at))) {
650  }
651  list newfields = NIL;
652  list fields = is_struct ? type_struct(entity_type(at)) : type_union(entity_type(at));
653  FOREACH(ENTITY, field, fields) {
654  char * ename;
655  asprintf(&ename,"%s" MODULE_SEP_STRING "struct_%d%s" , entity_local_name(cu), index -1, strrchr(entity_name(field),MEMBER_SEP_CHAR));
656  entity e = make_entity(ename,
657  copy_type(entity_type(field)),
659  copy_value(entity_initial(field))
660  );
661  newfields=CONS(ENTITY,e,newfields);
662  }
663  newfields=gen_nreverse(newfields);
664  type newet;
665  if(is_struct) newet = make_type_struct(newfields);
666  else newet = make_type_union(newfields);
667 
668  entity newe = make_entity(name, newet, copy_storage(entity_storage(at)), copy_value(entity_initial(at)));
670  type newt =
673  make_basic_derived(newe),
676  )
677  );
678  return newt;
679  }
680  }
681  return copy_type(t);
682 }
683 
684 /**
685  * Checks if an entity is in a list.
686  * Done by comparing the minimal user name.
687  */
689  if (ENDP(l))
690  return false;
691  FOREACH(entity, ent, l) {
693  return true;
694  }
695  return false;
696 }
697 
698 void outliner_parameters(entity new_fun, statement new_body, list referenced_entities,
699  hash_table entity_to_effective_parameter,
700  list *effective_parameters_, list *formal_parameters_)
701 {
702  string outline_module_name = (string)entity_user_name(new_fun);
703 
704 
705  /* all variables are promoted parameters */
706  list effective_parameters = *effective_parameters_;
707  list formal_parameters = *formal_parameters_;
708  intptr_t i=0;
709 
710  // Addition for R-Stream compatibility
711  // Prevent from adding a parameter if the entity is in the list
712  list induction_var = NIL;
713  // If no property activated then induction_var should stay to NIL
714  bool is_rstream = get_bool_property("OUTLINE_REMOVE_VARIABLE_RSTREAM_IMAGE") || get_bool_property("OUTLINE_REMOVE_VARIABLE_RSTREAM_SCOP");
715  if (is_rstream) {
716  // Enclosing loops map needed for get_variables_to_remove
718  get_variables_to_remove(referenced_entities, new_body, &induction_var);
720  // Adding the declarations to the new body
721  add_induction_var_to_local_declarations(&new_body, induction_var);
722  }
723 
724  FOREACH(ENTITY,e,referenced_entities)
725  {
726  if( (entity_variable_p(e) || entity_symbolic_p(e)) && (!is_entity_in_list(e, induction_var)))
727  {
728  pips_debug(6,"Add %s to outlined function parameters\n",entity_name(e));
729 
730  /* this create the dummy parameter */
731  entity dummy_entity = FindOrCreateEntity(
732  outline_module_name,
734  );
735  entity_initial(dummy_entity)=make_value_unknown();
736 
737  if(entity_symbolic_p(e))
738  entity_type(dummy_entity) = fortran_module_p(new_fun)?
741  else {
743  /* FI: when a new compilation unit is used, why
744  declare type in the *initial* compilation unit?
745  It generates derived types within the wrong
746  compilation unit... and back fires in the prettyprinter */
748  entity_type(dummy_entity)=copy_type(entity_type(e));
749  }
750 
751 
752  entity_storage(dummy_entity)=make_storage_formal(make_formal(dummy_entity,++i));
753 
754 
755  formal_parameters=CONS(PARAMETER,make_parameter(
756  copy_type(entity_type(dummy_entity)),
758  make_dummy_identifier(dummy_entity)),formal_parameters);
759 
760  /* this adds the effective parameter */
761  expression effective_parameter = (expression)hash_get(entity_to_effective_parameter,e);
762  if(effective_parameter == HASH_UNDEFINED_VALUE)
763  effective_parameter = entity_to_expression(e);
764 
765  effective_parameters=CONS(EXPRESSION,effective_parameter,effective_parameters);
766  }
767  /* this is a constant variable or fortran function result */
768  else if(entity_constant_p(e)||(fortran_module_p(new_fun) && entity_function_p(e))) {
769  AddLocalEntityToDeclarations(e,new_fun,new_body);
770  }
771 
772  }
773  *formal_parameters_= gen_nreverse(formal_parameters);
774  *effective_parameters_= gen_nreverse(effective_parameters);
775  hash_table_free(entity_to_effective_parameter);
776  gen_free_list(induction_var);
777  ifdebug(5) {
778  pips_debug(5,"Formals : \n");
779  print_parameters(*formal_parameters_);
780  pips_debug(5,"Effectives : \n");
781  print_expressions(*effective_parameters_);
782  }
783 }
784 
785  /* we need to patch parameters , effective parameters and body in C
786  * because parameters are passed by copy in function call
787  * it's not needed if
788  * - the parameter is only read (FI: or if it is written before it is read?)
789  * - it's an array / pointer
790  *
791  * Here a scalar will be passed by address and a prelude/postlude
792  * will be used in the outlined module as below :
793  *
794  * void new_module( int *scalar_0 ) {
795  * int scalar;
796  * scalar = *scalar_0;
797  * ...
798  * // Work on scalar
799  * ...
800  * *scalar_0 = scalar;
801  * }
802  *
803  * Note FI: this is also useless when the variable does not appear
804  * in the out region of the outlined piece of code. However, the
805  * out effets and out regions are not available for every piece of
806  * code.
807  *
808  */
809 void outliner_patch_parameters(list statements_to_outline, list referenced_entities, list effective_parameters, list formal_parameters,
810  statement new_body, statement begin, statement end)
811 {
812  list iter = effective_parameters;
813  list riter = referenced_entities;
814 
815  FOREACH(PARAMETER,p,formal_parameters)
816  {
817  expression x = EXPRESSION(CAR(iter));
818  entity re = ENTITY(CAR(riter));
822 
826  bool entity_written=false;
827  FOREACH(STATEMENT,stmt,statements_to_outline) {
828  bool write_p = find_write_effect_on_entity(stmt,ex);
829  ifdebug(5) {
830  if(write_p) {
831  pips_debug(5,"Entity %s written by statement (%d) : \n",entity_name(ex),the_current_debug_level);
833  }
834  }
835  entity_written|=write_p;
836  }
837 
838  if( (!basic_pointer_p(variable_basic(v))) &&
840  entity_written
841  )
842  {
846  CONS(DIMENSION,
849  NIL),
850  NIL)
851  );
852 
855 
856  //Change at call site (scalar=>&scalar)
857  syntax s = expression_syntax(x); // FIXME Leak ?
860 
861 
862  //Create prelude && postlude
864 
865  // FIXME : is it ok to alias dereferenced expression in 2 statements ?
868 
869  // Cheat on effects
872 
873 
874  insert_statement(begin,in,true);
875  insert_statement(end,out,false);
876 
877  /* e is no longer a formal parameter, but a local variable */
878  pips_debug(4,"Add declaration for %s",entity_name(e));
879 
880  /* storage eos = entity_storage(e); // e's old storage */
881  /* pips_assert("eos is a formal storage", storage_formal_p(eos)); */
882  /* formal fs = storage_formal(eos); */
883  /* entity f = formal_function(fs); // In fact, f is *not* a function but a variable! */
884  /* // No dependent type assumed, should be a scalar type */
885  /* // since a pointer had to be introduced */
886  /* entity a = module_to_dynamic_area(f); */
887  /* ram r = make_ram(f, a, UNKNOWN_RAM_OFFSET, NIL); */
888  /* storage ens = make_storage_ram(r); */
889  /* // add_C_variable_to_area() to fix the offset? */
890  /* entity_storage(e) = ens; */
891  /* free_storage(eos); */
892 
893  // We could add a push_generated_variable_commenter()
894  // to explain the generation
896  add_declaration_statement(new_body,e);
898  }
899  }
900  if(type_variable_p(entity_type(re))) {
904  convert_pointer_to_array(e,re,x,statements_to_outline);
905 
906  }
907  }
908  POP(iter);
909  POP(riter);
910  }
911  pips_assert("no effective parameter left", ENDP(iter));
912 }
913 
915  gen_remove(&loop_locals(l),e);
917 }
920 }
921 
922 static void outliner_compilation_unit(entity new_fun,
923  list formal_parameters __attribute__ ((unused))) {
924  if(get_bool_property("OUTLINE_INDEPENDENT_COMPILATION_UNIT")
926  string outline_module_name = (string)entity_user_name(new_fun);
927  char * the_cu = NULL,*iter, *cun;
928  if((iter=strchr(outline_module_name,FILE_SEP))) {
929  the_cu = strndup(outline_module_name,iter-outline_module_name);
930  }
931  else the_cu = strdup(outline_module_name);
932  asprintf(&cun,"%s" FILE_SEP_STRING, the_cu);
934  free(cun);
935  }
936 }
938  return !type_undefined_p(entity_type(e)) &&
940 }
941 
942 /* skipping anonymous enum ... */
943 static bool anonymous_type_p(entity e) {
944  const char * eln = entity_local_name(e);
945  return strstr(eln, DUMMY_STRUCT_PREFIX) || strstr(eln, DUMMY_UNION_PREFIX);
946 }
947 
948 static entity recursive_rename_types(entity e, const char * cun ) {
949  char * new_name;
950  asprintf(&new_name,"%s" MODULE_SEP_STRING "%s", cun, entity_local_name(e));
951  entity ne = gen_find_tabulated(new_name, entity_domain);
952  if(entity_undefined_p(ne))
953  ne = make_entity_copy_with_new_name(e, new_name, false);
954  free(new_name);
955  return ne;
956 }
957 
958 static
960  callees c = compute_callees(s);
961  entity cu = module_name_to_entity(cun);
962  /* first step : bring all typedefs and global declarations with you */
965  // do not forget dependent types ...
966  set tmp = set_dup(re);
967  SET_FOREACH(entity, rer, tmp) {
968  list of_entities = type_supporting_types(entity_type(rer));
969  FOREACH(ENTITY,e,of_entities) {
970  if( entity_field_p(e) ) /* special hook for struct member : consider their structure instead of the field */
972  set_add_element(re, re, e);
973  }
974  gen_free_list(of_entities);
975  }
976  set_free(tmp);
977  list lre = set_to_list(re);
979  set_free(re);
980  /* SG : part of this code is duplicated from inlining */
982  FOREACH(ENTITY, e, lre) {
983  if(!entity_enum_member_p(e) && /* enum member cannot be added to declarations */
984  !entity_formal_p(e) ) /* formal parameters are not considered */
985  {
988  {
989  if(anonymous_type_p(e)) continue;
990  if(top_level_entity_p(e)) {
991  if(get_bool_property("OUTLINE_ALLOW_GLOBALS")) {
994  }
995  }
996  else if(variable_static_p(e))
997  pips_internal_error("unhandled case : outlining a static variable\n");
998  else if(typedef_entity_p(e)) {
999  #if 0
1000  basic b = variable_basic(
1001  type_variable(
1002  entity_type(
1003  e
1004  )
1005  )
1006  );
1007  if(basic_derived_p(b)) {
1008  entity *et = &basic_derived(b);
1009  *et = recursive_rename_types(*et,cun);
1010  if(!anonymous_type_p(*et))
1011  AddEntityToCompilationUnit(*et, cu );
1012  }
1013  #endif
1014  e=recursive_rename_types(e,cun);
1016  }
1017  }
1018  }
1019  }
1020  }
1021  gen_free_list(lre);
1022 
1023  /* second step : bring all callers with you */
1025  char* new_name;
1027  asprintf(&new_name, "%s" MODULE_SEP_STRING"%s%s%s", cun, cun, get_string_property("OUTLINE_CALLEES_PREFIX"),entity_user_name(old_fun) );
1028  entity new_fun = make_entity(new_name,
1029  copy_type(entity_type(old_fun)),
1030  copy_storage(entity_storage(old_fun)),
1031  copy_value(entity_initial(old_fun))
1032  );
1035  replace_entity(s,old_fun, new_fun);
1036 
1037 
1039  outliner_independent_recursively(old_fun, cun, body);
1040 
1041  bool saved_order = get_bool_property(STAT_ORDER),
1042  saved_block = get_bool_property("PRETTYPRINT_BLOCKS");
1044  set_bool_property("PRETTYPRINT_BLOCKS",false);
1045  text t = text_named_module(new_fun, new_fun , body);
1046 
1048 
1049  /* horrible hack to prevent declaration duplication
1050  * signed : Serge Guelton
1051  */
1053  code_declarations(EntityCode(new_fun))=NIL;
1054 
1055  set_bool_property(STAT_ORDER,saved_order);
1056  set_bool_property("PRETTYPRINT_BLOCKS",saved_block);
1057  free_statement(body);
1058  }
1059  free_callees(c);
1060 }
1061 /**
1062  * redeclare all callees of outlined function in the same compilation unit
1063  */
1064 static
1065 void outliner_independent(const char * module_name, statement body) {
1066  if(get_bool_property("OUTLINE_INDEPENDENT_COMPILATION_UNIT")) {
1067  string cun;
1069  cun = strdup("");
1070  else {
1071  char * the_cu = NULL,*iter;
1072  if((iter=strchr(module_name,FILE_SEP))) {
1073  the_cu = strndup(module_name,iter-module_name);
1074  }
1075  else the_cu = strdup(module_name);
1076  asprintf(&cun,"%s" FILE_SEP_STRING, the_cu);
1077  free(the_cu);
1079  if(entity_undefined_p(cu))
1080  cu=MakeCompilationUnitEntity(cun);
1081  }
1083 
1085  {
1086  // Get DBR_CODE for the compilation unit
1087  if(!db_resource_required_or_available_p(DBR_PARSED_CODE,cun))
1088  {
1089  bool compilation_unit_parser(const char*);
1095  if(!entity_undefined_p(tmp))
1099  }
1100  if(!db_resource_required_or_available_p(DBR_CODE,cun))
1101  {
1102  bool controlizer(const char*);
1107  controlizer(cun);
1108  if(!entity_undefined_p(tmp))
1112  }
1113  statement cun_s=(statement)db_get_memory_resource(DBR_CODE, cun, true);
1114 
1115  // Update C_SOURCE_FILE from DBR_CODE
1117  text code_text = text_named_module(cu, cu, cun_s);
1118  string init_name = db_get_file_resource(DBR_C_SOURCE_FILE, cun, true);
1119  char *dir_name = db_get_current_workspace_directory();
1120 
1121  char *finit_name;
1122  asprintf(&finit_name,"%s/%s" ,dir_name, init_name);
1123  FILE *f = safe_fopen(finit_name, "w");
1124  print_text(f, code_text);
1125  safe_fclose(f, finit_name);
1126 
1127  db_touch_resource(DBR_C_SOURCE_FILE, cun);
1128  db_touch_resource(DBR_USER_FILE, cun);
1129 
1130  // Remove DBR_DECLARATIONS to force parsing from pipsmake
1131  db_delete_resource(DBR_DECLARATIONS, cun);
1132  }
1133  free(cun);
1134  }
1135 }
1136 
1137 
1138 void outliner_file(entity new_fun, list formal_parameters, statement *new_body)
1139 {
1140  string outline_module_name = (string)entity_user_name(new_fun);
1141 
1142  /* prepare parameters and body*/
1143  module_functional_parameters(new_fun)=formal_parameters;
1144  FOREACH(PARAMETER,p,formal_parameters) {
1148  }
1149 
1150  /* 5-0 : create new compilation unit */
1151  outliner_compilation_unit(new_fun, formal_parameters);
1152 
1155 
1156  /* 5-1 : add all callees to the same foreign compilation units */
1157  outliner_independent(outline_module_name, *new_body);
1158 
1159  /* 5-2: fix the types of the formal parameter in case a new
1160  compilation unit is used. Make sure that the function type and
1161  the types of the formal parameters are consistent. The function
1162  type is correct because the compilation unit has just been
1163  parsed. */
1164  if(false) {
1165  functional ft = type_functional(entity_type(new_fun));
1166  list fpl = functional_parameters(ft);
1167  int i, nparams = gen_length(fpl);
1168 
1169  for (i = 1; i <= nparams; i++) {
1170  entity param = find_ith_parameter(new_fun, i);
1171  type formal_pt = entity_type(param);
1172  type functional_pt = parameter_type(PARAMETER(CAR(fpl)));
1173  if(!type_equal_p(formal_pt, functional_pt)) {
1174  entity_type(param) = copy_type(functional_pt);
1175  }
1176  fpl = CDR(fpl);
1177  }
1178  }
1179 
1180  // In fortran we always want to generate the outline function
1181  // in its own new file
1182  char * cun = string_undefined;
1184  ;
1185  } else if(get_bool_property("OUTLINE_INDEPENDENT_COMPILATION_UNIT")) {
1186  // Declare in current module so that it's not undefined at call site
1187  char * the_cu = NULL,*iter;
1188  if((iter=strchr(outline_module_name,FILE_SEP))) {
1189  the_cu = strndup(outline_module_name,iter-outline_module_name);
1190  }
1191  else the_cu = strdup(outline_module_name);
1192  asprintf(&cun,"%s" FILE_SEP_STRING, the_cu);
1193  free(the_cu);
1194  }
1195  else {
1197  }
1198  /* add a return at the end of the body, in all cases */
1199  insert_statement(*new_body, make_return_statement(new_fun), false);
1200 
1201  /* we can now begin the outlining */
1202  bool saved_order = get_bool_property(STAT_ORDER),
1203  saved_block = get_bool_property("PRETTYPRINT_BLOCKS");
1205  set_bool_property("PRETTYPRINT_BLOCKS",false);
1206  text t = text_named_module(new_fun, new_fun /*get_current_module_entity()*/, *new_body);
1207 
1208 
1210  if(!string_undefined_p(cun)) free(cun);
1211  free_text(t);
1212 
1213  set_bool_property(STAT_ORDER,saved_order);
1214  set_bool_property("PRETTYPRINT_BLOCKS",saved_block);
1215 
1216 
1217 
1218  /* horrible hack to prevent declaration duplication
1219  * signed : Serge Guelton
1220  */
1222  code_declarations(EntityCode(new_fun))=NIL;
1223 
1224  /* we need to free them now, otherwise recompilation fails */
1225  FOREACH(PARAMETER,p,formal_parameters) {
1227  if(!type_undefined_p(entity_type(e)) &&
1228  entity_variable_p(e)) {
1229  free_type(entity_type(e));
1231  }
1232  }
1233 }
1234 
1235 statement outliner_call(entity new_fun, list statements_to_outline, list effective_parameters)
1236 {
1237 
1238  /* and return the replacement statement */
1239  instruction new_inst = make_instruction_call(make_call(new_fun,effective_parameters));
1240  statement new_stmt = statement_undefined;
1241 
1242  /* perform substitution :
1243  * replace the original statements by a single call
1244  * and patch the remaining statement (yes it's ugly)
1245  */
1246  FOREACH(STATEMENT,old_statement,statements_to_outline)
1247  {
1248  //free_instruction(statement_instruction(old_statement));
1249  if(statement_undefined_p(new_stmt))
1250  {
1251  statement_instruction(old_statement)=new_inst;
1252  new_stmt=old_statement;
1253  }
1254  else
1256  gen_free_list(statement_declarations(old_statement));
1257  statement_declarations(old_statement)=NIL;
1258  /* trash any extensions|comments, they may not be valid now */
1259  free_extensions(statement_extensions(old_statement));
1260  statement_extensions(old_statement)=empty_extensions();
1261  if(!string_undefined_p(statement_comments(old_statement))) free(statement_comments(old_statement));
1262  statement_comments(old_statement)=empty_comments;
1263 
1264  }
1265  return new_stmt;
1266 }
1267 
1268 void remove_from_formal_parameters(list induction_var, list* formal_parameters) {
1269  list form_par = gen_copy_seq(*formal_parameters);
1270  FOREACH(entity, ent, induction_var) {
1271  FOREACH(parameter, param, form_par) {
1272  dummy dum = parameter_dummy(param);
1273  entity param_ent = dummy_identifier(dum);
1274  if (!entity_undefined_p(ent) && !strcmp(entity_minimal_user_name(param_ent), entity_minimal_user_name(ent))) {
1275  printf("removing : \n");
1276  printf("formal parameter \n");
1277  printf("%s\n", entity_minimal_user_name(param_ent));
1278  printf("induction var\n");
1279  printf("%s\n", entity_minimal_user_name(ent));
1280  printf("\n\n");
1281  gen_remove_once(formal_parameters, param);
1282  }
1283  }
1284  }
1285  gen_free_list(form_par);
1286 }
1287 
1288 void remove_from_effective_parameters(list induction_var, list* effective_parameters) {
1289  list eff_par = gen_copy_seq(*effective_parameters);
1290  FOREACH(entity, ent, induction_var) {
1291  FOREACH(expression, exp, eff_par) {
1292  entity exp_ent = expression_to_entity(exp);
1293  if (!entity_undefined_p(exp_ent) && !strcmp(entity_minimal_user_name(exp_ent), entity_minimal_user_name(ent))) {
1294  printf("removing : \n");
1295  printf("effective parameter \n");
1296  printf("%s\n", entity_minimal_user_name(exp_ent));
1297  printf("induction var\n");
1298  printf("%s\n", entity_minimal_user_name(ent));
1299  printf("\n\n");
1300  gen_remove_once(effective_parameters, exp);
1301  }
1302  }
1303  }
1304  gen_free_list(eff_par);
1305 }
1306 
1309  FOREACH(entity, ent, induction_var) {
1310  *new_body = add_declaration_statement(*new_body, ent);
1311  }
1313 }
1314 
1315 /**
1316  * outline the statements in statements_to_outline into a module named outline_module_name
1317  * the outlined statements are replaced by a call to the newly generated module
1318  * statements_to_outline is modified in place to represent that call
1319  *
1320  * @param outline_module_name name of the new module
1321 
1322  * @param statements_to_outline is a list of consecutive statements to
1323  * outline into outline_module_name
1324  *
1325  * @return pointer to the newly generated statement (already inserted in statements_to_outline)
1326  */
1327 statement outliner(const char* outline_module_name, list statements_to_outline)
1328 {
1329  pips_assert("there are some statements to outline",!ENDP(statements_to_outline));
1331 
1332  statement new_body = make_block_statement(statements_to_outline);
1333 
1334  /* 1 : init */
1335  hash_table entity_to_effective_parameter = outliner_init(new_fun, statements_to_outline);
1336 
1337  /* pass loop bounds as parameters if required */
1338  const char* loop_label = get_string_property("OUTLINE_LOOP_BOUND_AS_PARAMETER");
1340  if(!statement_undefined_p(theloop) && statement_loop(theloop))
1341  outliner_extract_loop_bound(theloop,entity_to_effective_parameter);
1342 
1343  /* 2 : scan */
1344  list referenced_entities = outliner_scan(new_fun, statements_to_outline, new_body);
1345 
1346  /* 3 : parameters */
1347  list effective_parameters = NIL;
1348  list formal_parameters = NIL;
1349  outliner_parameters(new_fun, new_body, referenced_entities, entity_to_effective_parameter, &effective_parameters, &formal_parameters);
1350 
1351  /* 4 : patch parameters */
1353  && get_bool_property("OUTLINE_WRITTEN_SCALAR_BY_REFERENCE"))
1354  outliner_patch_parameters(statements_to_outline, referenced_entities, effective_parameters, formal_parameters, new_body, new_body, new_body);
1355 
1356  /* 5 : file */
1357  outliner_file(new_fun, formal_parameters, &new_body );
1358 
1359  /* 6 : call */
1360  statement new_stmt = outliner_call(new_fun, statements_to_outline, effective_parameters);
1361 
1362  /* 7: remove obsolete entities, this is needed otherwise the IR keeps some obsolete data */
1363  list declared_entities = statements_to_declarations(statements_to_outline);
1364  FOREACH(ENTITY,de,declared_entities) {
1365  FOREACH(STATEMENT, sde, statements_to_outline) {
1366  gen_context_multi_recurse(sde, de,
1369  NULL);
1371  free_entity(de);
1372  }
1373  }
1374  gen_free_list(declared_entities);
1375  return new_stmt;
1376 }
1377 
1378 /**
1379  * @brief entry point for outline module
1380  * outlining will be performed using either comment recognition
1381  * or interactively
1382  *
1383  * @param module_name name of the module containing the statements to outline
1384  */
1385 bool outline(const string module_name)
1386 {
1387  /* prelude */
1392 
1393  debug_on("OUTLINE_DEBUG_LEVEL");
1394 
1395  /* retrieve name of the outlined module */
1396  const char* outline_module_name = get_string_property_or_ask("OUTLINE_MODULE_NAME","outline module name ?\n");
1397 
1398  // Check the language. In case of Fortran the module name must be in
1399  // capital letters.
1400  char * omn=strdup(outline_module_name);
1402  omn=strupper(omn,omn);
1403 
1404  /* retrieve statement to outline */
1405  list statements_to_outline = find_statements_with_pragma(get_current_module_statement(),get_string_property("OUTLINE_PRAGMA")) ;
1406  if(ENDP(statements_to_outline)) {
1407  const char* label_name = get_string_property("OUTLINE_LABEL");
1408  if( empty_string_p(label_name) ) {
1410  }
1411  else {
1414  pips_user_error("Could not find loop labeled %s\n",label_name);
1415  if(statement_loop_p(statement_to_outline) && get_bool_property("OUTLINE_LOOP_STATEMENT"))
1417  statements_to_outline=make_statement_list(statement_to_outline);
1418  }
1419  }
1420 
1421  /* apply outlining */
1422  (void)outliner(omn,statements_to_outline);
1423  free(omn);
1424 
1425 
1426  debug_off();
1427 
1428  /* validate */
1433 
1434  /*postlude*/
1436  reset_rw_effects();
1439 
1440  return true;
1441 }
1442 /** @} */
1443 
float a2sf[2] __attribute__((aligned(16)))
USER generates a user error (i.e., non fatal) by printing the given MSG according to the FMT.
Definition: 3dnow.h:3
dummy make_dummy_identifier(entity _field_)
Definition: ri.c:620
call make_call(entity a1, list a2)
Definition: ri.c:269
value make_value_unknown(void)
Definition: ri.c:2847
basic make_basic_derived(entity _field_)
Definition: ri.c:182
parameter make_parameter(type a1, mode a2, dummy a3)
Definition: ri.c:1495
syntax make_syntax_call(call _field_)
Definition: ri.c:2500
expression make_expression(syntax a1, normalized a2)
Definition: ri.c:886
type make_type_union(list _field_)
Definition: ri.c:2733
subscript make_subscript(expression a1, list a2)
Definition: ri.c:2327
type make_type_variable(variable _field_)
Definition: ri.c:2715
void free_entity(entity p)
Definition: ri.c:2524
mode make_mode_reference(void)
Definition: ri.c:1356
type copy_type(type p)
TYPE.
Definition: ri.c:2655
basic copy_basic(basic p)
BASIC.
Definition: ri.c:104
void free_callees(callees p)
Definition: ri.c:194
type make_type_struct(list _field_)
Definition: ri.c:2730
basic make_basic_int(intptr_t _field_)
Definition: ri.c:158
basic make_basic_pointer(type _field_)
Definition: ri.c:179
statement copy_statement(statement p)
STATEMENT.
Definition: ri.c:2186
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
void free_extensions(extensions p)
Definition: ri.c:950
language copy_language(language p)
LANGUAGE.
Definition: ri.c:1202
dimension make_dimension(expression a1, expression a2, list a3)
Definition: ri.c:565
variable make_variable(basic a1, list a2, list a3)
Definition: ri.c:2895
instruction make_instruction_call(call _field_)
Definition: ri.c:1184
value copy_value(value p)
VALUE.
Definition: ri.c:2784
storage make_storage_formal(formal _field_)
Definition: ri.c:2282
void free_instruction(instruction p)
Definition: ri.c:1118
storage copy_storage(storage p)
STORAGE.
Definition: ri.c:2228
void free_type(type p)
Definition: ri.c:2658
void free_basic(basic p)
Definition: ri.c:107
mode make_mode_value(void)
Definition: ri.c:1353
void free_statement(statement p)
Definition: ri.c:2189
syntax make_syntax_subscript(subscript _field_)
Definition: ri.c:2509
formal make_formal(entity a1, intptr_t a2)
Definition: ri.c:1067
void free_text(text p)
Definition: text.c:74
bool db_resource_required_or_available_p(const char *rname, const char *oname)
from now on we must not know about the database internals?
Definition: database.c:505
bool db_touch_resource(const char *rname, const char *oname)
touch logical time for resource[owner], possibly behind the back of pipsdbm.
Definition: database.c:538
void db_delete_resource(const char *rname, const char *oname)
Delete a resource.
Definition: database.c:353
struct paramStruct params
void get_variables_to_remove(list, statement, list *)
misc.c
Definition: misc.c:58
bool has_entity_with_same_name(entity, list)
inlining.c
Definition: inlining.c:256
static FILE * out
Definition: alias_check.c:128
static statement module_statement
Definition: alias_check.c:125
struct _newgen_struct_expression_ * expression
Definition: alias_private.h:21
#define VALUE_ZERO
int Value
#define VALUE_ONE
bdt base
Current expression.
Definition: bdt_read_paf.c:100
bool compilation_unit_parser(const char *module_name)
Definition: c_parser.c:746
callees compute_callees(const statement stat)
Recompute the callees of a module statement.
Definition: callgraph.c:355
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
#define contrainte_succ(c)
#define contrainte_vecteur(c)
passage au champ vecteur d'une contrainte "a la Newgen"
bool controlizer(const char *)
The old controlizer user interface.
Definition: module.c:224
string compilation_unit_of_module(const char *)
The output is undefined if the module is referenced but not defined in the workspace,...
Definition: module.c:350
int dummy
A dummy file, to prevent empty libraries from breaking builds.
Definition: dummy.c:41
#define region_any_reference(reg)
To be avoided.
#define region_action(reg)
#define region_system(reg)
#define REGION
void set_rw_effects(statement_effects)
void set_cumulated_rw_effects(statement_effects)
void store_cumulated_rw_effects_list(statement, list)
list load_rw_effects_list(statement)
bool find_write_effect_on_entity(statement, entity)
void reset_cumulated_rw_effects(void)
void reset_rw_effects(void)
#define action_undefined
Definition: effects.h:277
#define action_write_p(x)
Definition: effects.h:314
#define action_read_p(x)
Definition: effects.h:311
bool empty_string_p(const char *s)
Definition: entity_names.c:239
const char * module_name(const char *s)
Return the module part of an entity name.
Definition: entity_names.c:296
void cleanup_subscripts(void *)
FILE * safe_fopen(const char *filename, const char *what)
Definition: file.c:67
char * get_string_property(const char *)
int safe_fclose(FILE *stream, const char *filename)
Definition: file.c:77
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
#define gen_chunk_undefined_p(c)
Definition: genC.h:75
#define gen_context_recurse(start, ctxt, domain_number, flt, rwt)
Definition: genC.h:285
#define STRING(x)
Definition: genC.h:87
void gen_full_free_list(list l)
Definition: genClib.c:1023
void free(void *)
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
void reset_current_module_statement(void)
Reset the current module statement.
Definition: static.c:221
const char * get_current_module_name(void)
Get the name of the current module.
Definition: static.c:121
statement set_current_module_statement(statement)
Set the current module statement.
Definition: static.c:165
statement get_current_module_statement(void)
Get the current module statement.
Definition: static.c:208
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
void replace_entity(void *s, entity old, entity new)
per variable version of replace_entities.
Definition: replace.c:113
void gen_recurse_stop(void *obj)
Tells the recursion not to go in this object.
Definition: genClib.c:3251
void gen_context_multi_recurse(void *o, void *context,...)
Multi-recursion with context function visitor.
Definition: genClib.c:3373
gen_chunk * gen_get_ancestor(int, const void *)
return the first ancestor object found of the given type.
Definition: genClib.c:3560
bool gen_true2(__attribute__((unused)) gen_chunk *u1, __attribute__((unused)) void *u2)
Definition: genClib.c:2785
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
instruction make_continue_instruction()
Creates a CONTINUE instruction, that is the FORTRAN nop, the ";" in C or the "pass" in Python for exa...
Definition: instruction.c:79
void clean_enclosing_loops(void)
Definition: loop.c:58
statement_mapping loops_mapping_of_statement(statement stat)
Definition: loop.c:155
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
void gen_remove(list *cpp, const void *o)
remove all occurences of item o from list *cpp, which is thus modified.
Definition: list.c:685
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
void gen_remove_once(list *pl, const void *o)
Remove the first occurence of o in list pl:
Definition: list.c:691
#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
void gen_list_and_not(list *a, const list b)
Compute A = A inter non B:
Definition: list.c:963
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
void * gen_find_eq(const void *item, const list seq)
Definition: list.c:422
list gen_append(list l1, const list l2)
Definition: list.c:471
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535
void gen_sort_list(list l, gen_cmp_func_t compare)
Sorts a list of gen_chunks in place, to avoid allocations...
Definition: list.c:796
bool gen_equals(const list l0, const list l1, gen_eq_func_t equals)
compares two lists using the functor given in parameters returns true if for all n,...
Definition: list.c:192
string db_get_memory_resource(const char *rname, const char *oname, bool pure)
Return the pointer to the resource, whatever it is.
Definition: database.c:755
#define DB_PUT_MEMORY_RESOURCE(res_name, own_name, res_val)
conform to old interface.
Definition: pipsdbm-local.h:66
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
bool statement_loop_p(statement)
Definition: statement.c:349
statement make_assign_statement(expression, expression)
Definition: statement.c:583
list statements_to_declarations(list)
Returns the declarations contained in a list of statement.
Definition: statement.c:3265
list statement_to_declarations(void *)
Get a list of all variables declared recursively within a statement.
Definition: statement.c:3253
list find_statements_with_pragma(statement, const char *)
Get a list of statements with pragma begining with a prefix.
Definition: statement.c:3912
void pop_generated_variable_commenter(void)
Definition: statement.c:2623
void insert_statement(statement, statement, bool)
This is the normal entry point.
Definition: statement.c:2570
statement make_return_statement(entity)
Definition: statement.c:779
statement add_declaration_statement(statement, entity)
Definition: statement.c:2790
statement find_statement_from_label_name(statement, const char *, const char *)
Definition: statement.c:3816
void push_generated_variable_commenter(string(*)(entity))
Definition: statement.c:2616
char end
Definition: gtk_status.c:82
hash_table hash_table_make(hash_key_type key_type, size_t size)
Definition: hash.c:294
void * hash_get(const hash_table htp, const void *key)
this function retrieves in the hash table pointed to by htp the couple whose key is equal to key.
Definition: hash.c:449
void hash_put(hash_table htp, const void *key, const void *val)
This functions stores a couple (key,val) in the hash table pointed to by htp.
Definition: hash.c:364
void hash_table_free(hash_table htp)
this function deletes a hash table that is no longer useful.
Definition: hash.c:327
static list indices
Definition: icm.c:204
void add_new_compilation_unit(const char *compilation_unit_name, bool is_fortran, entity module)
Warning! Do not modify this file that is automatically generated!
Definition: initializer.c:367
bool add_new_module_from_text(const char *module_name, text code_text, bool is_fortran, const char *compilation_unit_name)
Add the new resource files associated to a module with its more-or-less correct code.
Definition: initializer.c:431
#define debug_on(env)
Definition: misc-local.h:157
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145
#define asprintf
Definition: misc-local.h:225
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define pips_internal_error
Definition: misc-local.h:149
#define debug_off()
Definition: misc-local.h:160
#define pips_user_error
Definition: misc-local.h:147
int the_current_debug_level
Debugging functions.
Definition: debug.c:53
#define DUMMY_STRUCT_PREFIX
Definition: naming-local.h:87
#define STRUCT_PREFIX_CHAR
Definition: naming-local.h:57
#define FILE_SEP_STRING
Definition: naming-local.h:41
#define MEMBER_SEP_CHAR
Definition: naming-local.h:54
#define UNION_PREFIX_CHAR
Definition: naming-local.h:59
#define TOP_LEVEL_MODULE_NAME
Module containing the global variables in Fortran and C.
Definition: naming-local.h:101
#define FILE_SEP
Definition: naming-local.h:39
#define DUMMY_UNION_PREFIX
Definition: naming-local.h:88
#define MODULE_SEP_STRING
Definition: naming-local.h:30
const char * entity_minimal_user_name(entity e)
Do not preserve scope information.
Definition: naming.c:223
string strupper(string, const char *)
Definition: string.c:213
@ hash_pointer
Definition: newgen_hash.h:32
#define HASH_UNDEFINED_VALUE
value returned by hash_get() when the key is not found; could also be called HASH_KEY_NOT_FOUND,...
Definition: newgen_hash.h:56
#define HASH_DEFAULT_SIZE
Definition: newgen_hash.h:26
void * gen_find_tabulated(const char *, int)
Definition: tabulated.c:218
set set_assign_list(set, const list)
assigns a list contents to a set all duplicated elements are lost
Definition: set.c:474
set set_del_element(set, const set, const void *)
Definition: set.c:265
list set_to_list(const set)
create a list from a set the set is not freed
Definition: set.c:436
list set_to_sorted_list(const set, gen_cmp_func_t)
Definition: set.c:447
set set_difference(set, const set, const set)
Definition: set.c:256
#define SET_FOREACH(type_name, the_item, the_set)
enumerate set elements in their internal order.
Definition: newgen_set.h:78
void set_free(set)
Definition: set.c:332
bool set_belong_p(const set, const void *)
Definition: set.c:194
set set_union(set, const set, const set)
Definition: set.c:211
@ set_pointer
Definition: newgen_set.h:44
set set_dup(const set)
Definition: set.c:143
set set_make(set_type)
Create an empty set of any type but hash_private.
Definition: set.c:102
set set_add_element(set, const set, const void *)
Definition: set.c:152
#define string_undefined
Definition: newgen_types.h:40
char * string
STRING.
Definition: newgen_types.h:39
#define string_undefined_p(s)
Definition: newgen_types.h:41
bool(* gen_eq_func_t)(const void *, const void *)
Definition: newgen_types.h:115
int(* gen_cmp_func_t)(const void *, const void *)
Definition: newgen_types.h:114
int f(int off1, int off2, int n, float r[n], float a[n], float b[n])
Definition: offsets.c:15
static hash_table outliner_smart_references_computation(list outlined_statements, entity new_module)
purge the list of referenced entities by replacing calls to a[i][j] where i is a constant in statemen...
Definition: outlining.c:291
static string outlining_variable_commenter(__attribute__((unused)) entity e)
Definition: outlining.c:65
static bool entity_not_undefined_nor_constant_nor_intrinsic_p(entity e)
Definition: outlining.c:937
void outliner_patch_parameters(list statements_to_outline, list referenced_entities, list effective_parameters, list formal_parameters, statement new_body, statement begin, statement end)
we need to patch parameters , effective parameters and body in C because parameters are passed by cop...
Definition: outlining.c:809
static bool skip_constants_intrinsics_members(entity e)
Definition: outlining.c:129
static void check_private_variables_call_walker(call c, struct cpv *p)
Definition: outlining.c:169
static void do_remove_entity_from_decl(statement s, entity e)
Definition: outlining.c:918
static bool check_private_variables_loop_walker(loop l, struct cpv *p)
Definition: outlining.c:179
hash_table outliner_init(entity new_fun, list statements_to_outline)
Definition: outlining.c:546
static void outliner_smart_replacment(statement in, entity old, entity new, size_t nb_dims)
Definition: outlining.c:245
void remove_from_formal_parameters(list induction_var, list *formal_parameters)
Definition: outlining.c:1268
bool outline(const string module_name)
entry point for outline module outlining will be performed using either comment recognition or intera...
Definition: outlining.c:1385
static void outliner_extract_loop_bound(statement sloop, hash_table entity_to_effective_parameter)
Definition: outlining.c:453
static void outliner_independent_recursively(entity module, const char *cun, statement s)
Definition: outlining.c:959
static void convert_pointer_to_array(entity e, entity re, expression x, list statements)
Definition: outlining.c:494
static bool anonymous_type_p(entity e)
skipping anonymous enum ...
Definition: outlining.c:943
list outliner_scan(entity new_fun, list statements_to_outline, statement new_body)
Definition: outlining.c:555
void remove_from_effective_parameters(list induction_var, list *effective_parameters)
Definition: outlining.c:1288
static void convert_pointer_to_array_aux2(statement s, entity e)
Definition: outlining.c:489
static void get_loop_locals_and_remove_walker(statement st, set s)
Definition: outlining.c:77
static void outline_remove_duplicates(list *entities)
Definition: outlining.c:531
static bool skip_values(void *v)
Definition: outlining.c:125
static list private_variables(statement stat)
Definition: outlining.c:185
static set get_private_entities(statement st)
try hard to reproduce in / out regions with only loop_locals it is time to move to regions ....
Definition: outlining.c:115
void add_induction_var_to_local_declarations(statement *new_body, list induction_var)
Definition: outlining.c:1307
static void outliner_independent(const char *module_name, statement body)
redeclare all callees of outlined function in the same compilation unit
Definition: outlining.c:1065
static void do_outliner_smart_replacment(reference r, ocontext_t *ctxt)
Definition: outlining.c:209
list outliner_statements_referenced_entities(list statements)
outlining.c
Definition: outlining.c:251
static string outlining_patched_variable_commenter(__attribute__((unused)) entity e)
Definition: outlining.c:70
static type type_to_named_type(type t, entity cu)
create a new type from given type, eventually renaming unnamed structures inside all new entities gen...
Definition: outlining.c:631
statement outliner_call(entity new_fun, list statements_to_outline, list effective_parameters)
Definition: outlining.c:1235
void outliner_file(entity new_fun, list formal_parameters, statement *new_body)
Definition: outlining.c:1138
void outliner_parameters(entity new_fun, statement new_body, list referenced_entities, hash_table entity_to_effective_parameter, list *effective_parameters_, list *formal_parameters_)
Definition: outlining.c:698
static void do_remove_entity_from_private(loop l, entity e)
Definition: outlining.c:914
static list statements_localize_declarations(list statements, entity module, statement module_statement)
Definition: outlining.c:420
static set get_loop_locals_and_remove(statement st)
Definition: outlining.c:105
static void outliner_compilation_unit(entity new_fun, list formal_parameters __attribute__((unused)))
Definition: outlining.c:922
statement outliner(const char *outline_module_name, list statements_to_outline)
outline the statements in statements_to_outline into a module named outline_module_name the outlined ...
Definition: outlining.c:1327
static entity recursive_rename_types(entity e, const char *cun)
Definition: outlining.c:948
static void convert_pointer_to_array_aux(expression exp, entity e)
Definition: outlining.c:469
static void sort_entities_with_dep(list *l)
Definition: outlining.c:136
#define STAT_ORDER
Definition: outlining.c:75
bool is_entity_in_list(entity e, list l)
Checks if an entity is in a list.
Definition: outlining.c:688
void print_parameters(list lp)
Display a parameter on stderr, useful for debugging.
Definition: parameter.c:63
void unnormalize_expression(void *st)
void unnormalize_expression(expression exp): puts all the normalized field of expressions in "st" to ...
Definition: normalize.c:452
static char * module
Definition: pips.c:74
#define db_get_file_resource
string db_get_current_workspace_directory(void)
Definition: workspace.c:96
void print_expressions(list le)
Definition: expression.c:98
text text_named_module(entity, entity, statement)
list find_statements_interactively(statement)
prompt the user to select contiguous statement in s
Definition: statement.c:258
void print_statement(statement)
Print a statement on stderr.
Definition: statement.c:98
bool same_entity_lname_p(entity, entity)
Definition: same_names.c:64
void set_bool_property(const char *, bool)
const char * get_string_property_or_ask(const char *, const char[])
#define X
Definition: r1.c:42
bool module_reorder(statement body)
Reorder a module and recompute order to statement if any.
Definition: reorder.c:244
#define make_expression_list(stats...)
#define MINUS_OPERATOR_NAME
#define PLUS_OPERATOR_NAME
#define DEFAULT_INTEGER_TYPE_SIZE
#define INSTANCE_OF(type, value)
polymorhism thanks to newgen !
#define make_entity(n, t, s, i)
#define DEREFERENCING_OPERATOR_NAME
Definition: ri-util-local.h:93
#define entity_symbolic_p(e)
#define expression_scalar_p(e)
#define entity_declarations(e)
MISC: newgen shorthands.
#define ADDRESS_OF_OPERATOR_NAME
#define entity_variable_p(e)
An entity_variable_p(e) may hide a typedef and hence a functional type.
#define module_language(e)
implemented as a macro to allow lhs
#define make_statement_list(stats...)
easy list constructor
#define empty_comments
Empty comments (i.e.
#define module_functional_parameters(func)
#define entity_constant_p(e)
bool entity_not_constant_or_intrinsic_p(entity e)
Default entity filter for get_referenced_entities()
Definition: entity.c:3050
const char * entity_user_name(entity e)
Since entity_local_name may contain PIPS special characters such as prefixes (label,...
Definition: entity.c:487
bool entity_enum_member_p(entity e)
Definition: entity.c:980
entity FindEntity(const char *package, const char *name)
Retrieve an entity from its package/module name and its local name.
Definition: entity.c:1503
const char * entity_local_name(entity e)
entity_local_name modified so that it does not core when used in vect_fprint, since someone thought t...
Definition: entity.c:453
entity FindOrCreateEntity(const char *package, const char *local_name)
Problem: A functional global entity may be referenced without parenthesis or CALL keyword in a functi...
Definition: entity.c:1586
int compare_entities(const entity *pe1, const entity *pe2)
Comparison function for qsort.
Definition: entity.c:1328
bool entity_formal_p(entity p)
is p a formal parameter?
Definition: entity.c:1935
bool same_entity_p(entity e1, entity e2)
predicates on entities
Definition: entity.c:1321
bool c_module_p(entity m)
Test if a module "m" is written in C.
Definition: entity.c:2777
code entity_code(entity e)
Definition: entity.c:1098
set get_referenced_entities_filtered(void *elem, bool(*chunk_filter)(void *), bool(*entity_filter)(entity))
Same as get_referenced_entities, but will only consider entities that fulfills entity_filter and will...
Definition: entity.c:2982
entity module_name_to_entity(const char *mn)
This is an alias for local_name_to_top_level_entity.
Definition: entity.c:1479
entity make_empty_subroutine(const char *name, language l)
Definition: entity.c:268
bool entity_function_p(entity e)
Definition: entity.c:724
bool typedef_entity_p(entity e)
Definition: entity.c:1902
basic entity_basic(entity e)
return the basic associated to entity e if it's a function/variable/constant basic_undefined otherwis...
Definition: entity.c:1380
bool entity_field_p(entity e)
e is the field of a structure
Definition: entity.c:857
void print_entities(list l)
Definition: entity.c:167
code EntityCode(entity e)
this function checks that e has an initial value code.
Definition: entity.c:301
bool fortran_module_p(entity m)
Test if a module is in Fortran.
Definition: entity.c:2799
bool top_level_entity_p(entity e)
Check if the scope of entity e is global.
Definition: entity.c:1130
entity entity_field_to_entity_struct_or_union(entity f)
Definition: entity.c:925
bool member_entity_p(entity e)
Definition: entity.c:1921
entity MakeCompilationUnitEntity(const char *name)
This is useful for the C language only.
Definition: entity.c:1954
set get_referenced_entities(void *elem)
retrieves the set of entities used in elem beware that this entities may be formal parameters,...
Definition: entity.c:3063
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
entity make_entity_copy_with_new_name(entity e, string global_new_name, bool move_initialization_p)
Create a copy of an entity, with (almost) identical type, storage and initial value if move_initializ...
Definition: entity.c:2463
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
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
void update_expression_syntax(expression e, syntax s)
frees expression syntax of e and replace it by the new syntax s
Definition: expression.c:3564
expression int_to_expression(_int i)
transform an int into an expression and generate the corresponding entity if necessary; it is not cle...
Definition: expression.c:1188
expression MakeUnaryCall(entity f, expression a)
Creates a call expression to a function with one argument.
Definition: expression.c:342
bool expression_reference_p(expression e)
Test if an expression is a reference.
Definition: expression.c:528
reference expression_reference(expression e)
Short cut, meaningful only if expression_reference_p(e) holds.
Definition: expression.c:1832
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
bool same_expression_p(expression e1, expression e2)
this is slightly different from expression_equal_p, as it will return true for a+b vs b+a
Definition: expression.c:1426
extensions empty_extensions(void)
extension.c
Definition: extension.c:43
basic basic_of_expression(expression)
basic basic_of_expression(expression exp): Makes a basic of the same basic as the expression "exp".
Definition: type.c:1383
bool array_type_p(type)
Definition: type.c:2942
list type_supporting_types(type)
Return the list of types used to define type t.
Definition: type.c:5203
void AddLocalEntityToDeclarations(entity, entity, statement)
Add the variable entity e to the list of variables of the function module.
Definition: variable.c:233
entity make_new_array_variable_with_prefix(const char *, entity, basic, list)
J'ai ameliore la fonction make_new_scalar_variable_with_prefix
Definition: variable.c:785
entity make_new_scalar_variable(entity, basic)
Definition: variable.c:741
bool type_equal_p(type, type)
Definition: type.c:547
type pointed_type(type)
returns the type pointed by the input type if it is a pointer or an array of pointers
Definition: type.c:3035
bool formal_parameter_p(entity)
Definition: variable.c:1489
entity make_new_scalar_variable_with_prefix(const char *, entity, basic)
Create a new scalar variable of type b in the given module.
Definition: variable.c:592
void set_enclosing_loops_map(statement_mapping)
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
entity find_ith_parameter(entity, int)
Definition: util.c:93
#define dummy_identifier(x)
Definition: ri.h:1033
#define loop_body(x)
Definition: ri.h:1644
#define type_struct(x)
Definition: ri.h:2964
#define basic_pointer(x)
Definition: ri.h:637
#define normalized_undefined
Definition: ri.h:1745
#define expression_domain
newgen_execution_domain_defined
Definition: ri.h:154
#define functional_result(x)
Definition: ri.h:1444
#define parameter_dummy(x)
Definition: ri.h:1823
#define parameter_type(x)
Definition: ri.h:1819
#define callees_callees(x)
Definition: ri.h:675
#define reference_variable(x)
Definition: ri.h:2326
#define loop_domain
newgen_language_domain_defined
Definition: ri.h:218
#define basic_derived(x)
Definition: ri.h:640
#define code_externs(x)
Definition: ri.h:790
#define range_upper(x)
Definition: ri.h:2290
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define type_functional(x)
Definition: ri.h:2952
#define type_variable(x)
Definition: ri.h:2949
#define basic_pointer_p(x)
Definition: ri.h:635
#define basic_derived_p(x)
Definition: ri.h:638
#define 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
#define call_domain
newgen_callees_domain_defined
Definition: ri.h:58
#define basic_overloaded_p(x)
Definition: ri.h:623
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define instruction_undefined
Definition: ri.h:1454
#define type_undefined_p(x)
Definition: ri.h:2884
#define entity_undefined_p(x)
Definition: ri.h:2762
#define reference_domain
newgen_range_domain_defined
Definition: ri.h:338
#define entity_undefined
Definition: ri.h:2761
#define expression_undefined
Definition: ri.h:1223
#define entity_name(x)
Definition: ri.h:2790
#define functional_parameters(x)
Definition: ri.h:1442
#define PARAMETER(x)
PARAMETER.
Definition: ri.h:1788
#define reference_indices(x)
Definition: ri.h:2328
#define statement_extensions(x)
Definition: ri.h:2464
#define value_code(x)
Definition: ri.h:3067
#define variable_qualifiers(x)
Definition: ri.h:3124
#define loop_label(x)
Definition: ri.h:1646
#define loop_locals(x)
Definition: ri.h:1650
#define expression_undefined_p(x)
Definition: ri.h:1224
#define variable_dimensions(x)
Definition: ri.h:3122
#define statement_declarations(x)
Definition: ri.h:2460
#define statement_instruction(x)
Definition: ri.h:2458
#define syntax_undefined
Definition: ri.h:2676
#define statement_comments(x)
Definition: ri.h:2456
#define type_undefined
Definition: ri.h:2883
#define loop_range(x)
Definition: ri.h:1642
#define storage_rom_p(x)
Definition: ri.h:2525
#define statement_undefined_p(x)
Definition: ri.h:2420
#define entity_type(x)
Definition: ri.h:2792
#define expression_syntax(x)
Definition: ri.h:1247
#define language_fortran_p(x)
Definition: ri.h:1591
#define type_variable_p(x)
Definition: ri.h:2947
#define entity_domain
newgen_syntax_domain_defined
Definition: ri.h:410
#define loop_index(x)
Definition: ri.h:1640
#define type_union(x)
Definition: ri.h:2967
#define variable_basic(x)
Definition: ri.h:3120
#define statement_undefined
Definition: ri.h:2419
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
#define entity_initial(x)
Definition: ri.h:2796
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...
char * strdup()
int printf()
void vect_chg_sgn(Pvecteur v)
void vect_chg_sgn(Pvecteur v): multiplie v par -1
Definition: scalaires.c:151
list statement_to_outline
scalopragma.c
Definition: scalopragma.c:25
#define ifdebug(n)
Definition: sg.c:47
static char * x
Definition: split_file.c:159
#define intptr_t
Definition: stdint.in.h:294
char * strndup(char const *s, size_t n)
A replacement function, for systems that lack strndup.
Definition: strndup.c:26
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
FI: I do not understand why the type is duplicated at the set level.
Definition: set.c:59
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: outlining.c:162
entity e
Definition: outlining.c:163
bool rm
Definition: outlining.c:164
size_t nb_dims
Definition: outlining.c:207
entity old
Definition: outlining.c:205
entity new
Definition: outlining.c:206
Definition: replace.c:135
Definition: statement.c:54
bool clone(const string)
void print_text(FILE *fd, text t)
Definition: print.c:195
A gen_chunk is used to store every object.
Definition: genC.h:58
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207
#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
void vect_rm(Pvecteur v)
void vect_rm(Pvecteur v): desallocation des couples de v;
Definition: alloc.c:78
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
void AddEntityToCompilationUnit(entity e, entity cu)
Add an entity to the current's module compilation unit declarations we have to generate its statement...
Definition: module.c:198
void AddEntityToModuleCompilationUnit(entity e, entity module)
Definition: module.c:301
entity module_entity_to_compilation_unit_entity(entity m)
Retrieve the compilation unit containing a module definition.
Definition: module.c:116