PIPS
declarations.c File Reference
#include <stdlib.h>
#include <stdio.h>
#include <string.h>
#include "linear.h"
#include "genC.h"
#include "misc.h"
#include "properties.h"
#include "ri-util.h"
+ Include dependency graph for declarations.c:

Go to the source code of this file.

Functions

void check_fortran_declaration_dependencies (list ldecl)
 Regeneration of declarations from the symbol table. More...
 
list get_common_members (entity common, entity __attribute__((unused)) module, bool __attribute__((unused)) only_primary)
 The fprint_functional() and fprint_environment() functions are moved from syntax/declaration.c. More...
 
void print_C_common_layout (FILE *fd, entity c, bool debug_p)
 
void fprint_functional (FILE *fd, functional f)
 This function is called from c_parse() via ResetCurrentModule() and fprint_environment() More...
 
void fprint_environment (FILE *fd, entity m)
 
void fprint_C_environment (FILE *fd, entity m)
 
void fprint_any_environment (FILE *fd, entity m, bool is_fortran)
 
void split_initializations_in_statement (statement s)
 Transform a declaration with an initialization statement into 2 parts, a declaration statement and an initializer statement. More...
 
void dump_functional (functional f, string_buffer result)
 

Function Documentation

◆ check_fortran_declaration_dependencies()

void check_fortran_declaration_dependencies ( list  ldecl)

Regeneration of declarations from the symbol table.

declarations.c

Regeneration of declarations... #define LIST_SEPARATOR (is_fortran? ", " : ",")

Check that each declaration only depends on previous declarations

FOREACH(ENTITY, dv, dep) {

Formal parameters are put in ldecl right away when parsing the SUBROUTINE or FUNCTION statement. The placement of their actual declaration is unknown. They may depend on PARAMETERs declared later

Should be a ParserError() when called from ProcessEntries()...

Parameters
ldecldecl

Definition at line 47 of file declarations.c.

48 {
49  /* Check that each declaration only depends on previous declarations */
50  int r = 1;
51 
52  FOREACH(ENTITY, v, ldecl) {
53  type t = entity_type(v);
54 
55  if(type_variable_p(t)) {
57  list cdep = list_undefined;
58  storage vs = entity_storage(v);
59 
60  /* FOREACH(ENTITY, dv, dep) { */
61  for(cdep = dep; !ENDP(cdep); POP(cdep)) {
62  entity dv = ENTITY(CAR(cdep));
63  int dr = gen_position(dv, ldecl);
64  value dvv = entity_initial(dv);
65 
66  if(storage_formal_p(vs) && value_symbolic_p(dvv)) {
67  /* Formal parameters are put in ldecl right away when
68  parsing the SUBROUTINE or FUNCTION statement. The
69  placement of their actual declaration is unknown. They
70  may depend on PARAMETERs declared later */
71  ;
72  }
73  else if(dr>=r) {
74  if(entity_symbolic_p(dv))
75  pips_user_warning("Fortran declaration order may be violated. "
76  "Variable \"%s\" depends on parameter \"%s\""
77  " but is, at least partly, declared first.\n",
79  else if(entity_scalar_p(dv))
80  pips_user_warning("Fortran declaration order may be violated. "
81  "Variable \"%s\" depends on variable \"%s\" "
82  "but is, at least partly, declared first.\n",
84  else
85  /* Should be a ParserError() when called from ProcessEntries()... */
86  pips_user_error("Fortran declaration order violated. Variable \"%s\" "
87  "depends on variable \"%s\" but is declared first.\n",
89  }
90  }
91  gen_free_list(dep);
92  }
93  r++;
94  }
95 }
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
int gen_position(const void *item, const list l)
Element ranks are strictly positive as for first, second, and so on.
Definition: list.c:995
#define POP(l)
Modify a list pointer to point on the next element of the list.
Definition: newgen_list.h:59
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
#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 list_undefined
Undefined list definition :-)
Definition: newgen_list.h:69
#define pips_user_warning
Definition: misc-local.h:146
#define pips_user_error
Definition: misc-local.h:147
#define entity_symbolic_p(e)
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_scalar_p(entity)
The concrete type of e is a scalar type.
Definition: variable.c:1113
list fortran_type_supporting_entities(list, type)
Definition: type.c:4593
#define storage_formal_p(x)
Definition: ri.h:2522
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define entity_storage(x)
Definition: ri.h:2794
#define value_symbolic_p(x)
Definition: ri.h:3068
#define entity_type(x)
Definition: ri.h:2792
#define type_variable_p(x)
Definition: ri.h:2947
#define entity_initial(x)
Definition: ri.h:2796
The structure used to build lists in NewGen.
Definition: newgen_list.h:41

References CAR, ENDP, ENTITY, entity_initial, entity_scalar_p(), entity_storage, entity_symbolic_p, entity_type, entity_user_name(), FOREACH, fortran_type_supporting_entities(), gen_free_list(), gen_position(), list_undefined, NIL, pips_user_error, pips_user_warning, POP, storage_formal_p, type_variable_p, and value_symbolic_p.

Referenced by text_entity_declaration().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ dump_functional()

void dump_functional ( functional  f,
string_buffer  result 
)

FI: we could do nothing or put "void". I choose to put "void" to give more information about the internal representation.

NL

NL

NL

An argument can be functional, but not (yet) a result.

Parameters
resultesult

Definition at line 581 of file declarations.c.

582 {
583  type tr = functional_result(f);
584  bool first = true;
585 
587  {
588  type ta = parameter_type(p);
589 
590  if (first)
591  first = false;
592  else
593  string_buffer_append(result, " x ");
594 
595  pips_assert("Argument type is variable or varags:variable or functional or void",
596  type_variable_p(ta)
598  || type_functional_p(ta)
599  || type_void_p(ta));
600 
601  if (type_variable_p(ta)) {
602  variable v = type_variable(ta);
603  basic b = variable_basic(v);
606  string_buffer_append(result, "(");
607  dump_functional(f,result);
608  string_buffer_append(result, ") *");
609  }
610  else {
612  int ndims = gen_length(variable_dimensions(v));
613  for (int i = 0; i < ndims; i++)
614  string_buffer_append(result, "[]");
615  }
616  }
617  else if(type_functional_p(ta)) {
618  functional fa = type_functional(ta);
619 
620  string_buffer_append(result, "(");
621  dump_functional(fa, result);
622  string_buffer_append(result, ")");
623  }
624  else if(type_varargs_p(ta)) {
625  string_buffer_append(result, concatenate(type_to_string(ta),":",NULL));
626  ta = type_varargs(ta);
627  string_buffer_append(result,
629  }
630  else if(type_void_p(ta)) {
631  /* FI: we could do nothing or put "void". I choose to put "void"
632  to give more information about the internal
633  representation. */
635  }
636  }
637 
639  string_buffer_append(result, concatenate("()",NULL));
640  }
641 
642  string_buffer_append(result, concatenate(" -> ",NULL));
643 
644  if(type_variable_p(tr))
645  string_buffer_append(result,
647  /*,NL*/,NULL));
648  else if(type_void_p(tr))
649  string_buffer_append(result, concatenate(type_to_string(tr)/*,NL*/,NULL));
650  else if(type_unknown_p(tr)){
651  string_buffer_append(result, concatenate(type_to_string(tr)/*,NL*/,NULL));
652  }
653  else if(type_varargs_p(tr)) {
654  string_buffer_append(result,
655  concatenate(type_to_string(tr),":",
657  }
658  else
659  /* An argument can be functional, but not (yet) a result. */
660  pips_internal_error("Ill. type %d", type_tag(tr));
661 }
size_t gen_length(const list l)
Definition: list.c:150
#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
string concatenate(const char *,...)
Return the concatenation of the given strings.
Definition: string.c:183
void string_buffer_append(string_buffer, const string)
append string s (if non empty) to string buffer sb, the duplication is done if needed according to th...
int f(int off1, int off2, int n, float r[n], float a[n], float b[n])
Definition: offsets.c:15
string basic_to_string(basic)
Definition: type.c:87
void dump_functional(functional f, string_buffer result)
Definition: declarations.c:581
string type_to_string(const type)
type.c
Definition: type.c:51
#define type_functional_p(x)
Definition: ri.h:2950
#define basic_pointer(x)
Definition: ri.h:637
#define functional_result(x)
Definition: ri.h:1444
#define parameter_type(x)
Definition: ri.h:1819
#define type_unknown_p(x)
Definition: ri.h:2956
#define type_tag(x)
Definition: ri.h:2940
#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 type_void_p(x)
Definition: ri.h:2959
#define type_varargs(x)
Definition: ri.h:2955
#define functional_parameters(x)
Definition: ri.h:1442
#define type_varargs_p(x)
Definition: ri.h:2953
#define variable_dimensions(x)
Definition: ri.h:3122
#define variable_basic(x)
Definition: ri.h:3120

References basic_pointer, basic_pointer_p, basic_to_string(), concatenate(), ENDP, f(), FOREACH, functional_parameters, functional_result, gen_length(), parameter_type, pips_assert, pips_internal_error, string_buffer_append(), type_functional, type_functional_p, type_tag, type_to_string(), type_unknown_p, type_varargs, type_varargs_p, type_variable, type_variable_p, type_void_p, variable_basic, and variable_dimensions.

Referenced by get_symbol_table(), and words_type().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ fprint_any_environment()

void fprint_any_environment ( FILE *  fd,
entity  m,
bool  is_fortran 
)

rank of formal parameter

return variable

To simplify validation, at the expense of some information about the parsing process.

In C, no return entity is created (yet). See MakeCurrentModule().

List of implicitly and explicitly declared variables, functions and areas

List of external variables and functions and areas

Formal parameters

Return variable

Structure of each area/common

Parameters
fdd
is_fortrans_fortran

Definition at line 297 of file declarations.c.

298 {
300  int nth = 0; /* rank of formal parameter */
301  entity rv = entity_undefined; /* return variable */
302 
303  pips_assert("fprint_environment", entity_module_p(m));
304 
305  /* To simplify validation, at the expense of some information about
306  the parsing process. */
308 
309  (void) fprintf(fd, "\nDeclarations for module %s with type ",
310  module_local_name(m));
312  (void) fprintf(fd, "\n\n");
313 
314  /* In C, no return entity is created (yet). See MakeCurrentModule(). */
315  pips_assert("A module storage is ROM or return",
318 
319  /* List of implicitly and explicitly declared variables,
320  functions and areas */
321 
322  (void) fprintf(fd, "%s\n", ENDP(decls)?
323  "* empty declaration list *\n\n": "Variable list:\n\n");
324 
325  MAP(ENTITY, e, {
326  type t = entity_type(e);
327 
328  fprintf(fd, "Declared entity %s\twith type %s ", entity_name(e), type_to_string(t));
329 
330  if(type_variable_p(t))
332  else if(type_functional_p(t)) {
334  }
335  else if(type_area_p(t)) {
336  (void) fprintf(fd, "with size %td\n", area_size(type_area(t)));
337  }
338  else
339  (void) fprintf(fd, "\n");
340  },
341  decls);
342 
343  if(!is_fortran) {
345  /* List of external variables and functions and areas */
346 
348 
349  (void) fprintf(fd, "%s\n", ENDP(edecls)?
350  "* empty external declaration list *\n\n": "External variable list:\n\n");
351 
352  MAP(ENTITY, e, {
353  type t = entity_type(e);
354 
355  fprintf(fd, "Declared entity %s\twith type %s ", entity_name(e), type_to_string(t));
356 
357  if(type_variable_p(t))
359  else if(type_functional_p(t)) {
361  }
362  else if(type_area_p(t)) {
363  (void) fprintf(fd, "with size %td\n", area_size(type_area(t)));
364  }
365  else
366  (void) fprintf(fd, "\n");
367  },
368  edecls);
369  gen_free_list(edecls);
370  }
371 
372  /* Formal parameters */
373  nth = 0;
374  MAP(ENTITY, v, {
375  storage vs = entity_storage(v);
376 
377  pips_assert("All storages are defined", !storage_undefined_p(vs));
378 
379  if(storage_formal_p(vs)) {
380  nth++;
381  if(nth==1) {
382  (void) fprintf(fd, "\nLayouts for formal parameters:\n\n");
383  }
384  (void) fprintf(fd,
385  "\tVariable %s,\toffset = %td\n",
387  }
388  else if(storage_return_p(vs)) {
389  pips_assert("No more than one return variable", entity_undefined_p(rv));
390  rv = v;
391  }
392  }, decls);
393 
394  /* Return variable */
395  if(!entity_undefined_p(rv))
396  {
397  int asize;
398  if (!SizeOfArray(rv, &asize))
399  asize = -1;
400  fprintf(fd,
401  "\nLayout for return variable:\n\n"
402  "\tVariable %s,\tsize = %d\n", entity_name(rv), asize);
403  }
404 
405  /* Structure of each area/common */
406  if(!ENDP(decls)) {
407  (void) fprintf(fd, "\nLayouts for areas (commons):\n\n");
408  }
409 
410  MAP(ENTITY, e, {
411  if(type_area_p(entity_type(e))) {
412  if(is_fortran)
413  print_common_layout(fd, e, false);
414  else
415  print_C_common_layout(fd, e, false);
416  }
417  },
418  decls);
419 
420  (void) fprintf(fd, "End of declarations for module %s\n\n",
421  module_local_name(m));
422 
423  gen_free_list(decls);
424 }
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
#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
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
int(* gen_cmp_func_t)(const void *, const void *)
Definition: newgen_types.h:114
void print_common_layout(FILE *fd, entity c, bool debug_p)
Definition: area.c:207
void print_C_common_layout(FILE *fd, entity c, bool debug_p)
Definition: declarations.c:129
void fprint_functional(FILE *fd, functional f)
This function is called from c_parse() via ResetCurrentModule() and fprint_environment()
Definition: declarations.c:227
int compare_entities(const entity *pe1, const entity *pe2)
Comparison function for qsort.
Definition: entity.c:1328
const char * module_local_name(entity e)
Returns the module local user name.
Definition: entity.c:582
bool entity_module_p(entity e)
Definition: entity.c:683
bool SizeOfArray(entity, int *)
This function computes the total size of a variable in bytes, ie.
Definition: size.c:87
#define formal_offset(x)
Definition: ri.h:1408
#define area_size(x)
Definition: ri.h:544
#define code_externs(x)
Definition: ri.h:790
#define code_declarations(x)
Definition: ri.h:784
#define storage_formal(x)
Definition: ri.h:2524
#define entity_undefined_p(x)
Definition: ri.h:2762
#define entity_undefined
Definition: ri.h:2761
#define entity_name(x)
Definition: ri.h:2790
#define value_code(x)
Definition: ri.h:3067
#define type_area(x)
Definition: ri.h:2946
#define type_area_p(x)
Definition: ri.h:2944
#define storage_rom_p(x)
Definition: ri.h:2525
#define storage_return_p(x)
Definition: ri.h:2516
#define storage_undefined_p(x)
Definition: ri.h:2477
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...

References area_size, basic_to_string(), code_declarations, code_externs, compare_entities(), ENDP, ENTITY, entity_initial, entity_module_p(), entity_name, entity_storage, entity_type, entity_undefined, entity_undefined_p, formal_offset, fprint_functional(), fprintf(), gen_copy_seq(), gen_free_list(), gen_sort_list(), MAP, module_local_name(), pips_assert, print_C_common_layout(), print_common_layout(), SizeOfArray(), storage_formal, storage_formal_p, storage_return_p, storage_rom_p, storage_undefined_p, type_area, type_area_p, type_functional, type_functional_p, type_to_string(), type_variable, type_variable_p, value_code, and variable_basic.

Referenced by fprint_C_environment(), and fprint_environment().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ fprint_C_environment()

void fprint_C_environment ( FILE *  fd,
entity  m 
)
Parameters
fdd

Definition at line 292 of file declarations.c.

293 {
294  fprint_any_environment(fd, m, false);
295 }
void fprint_any_environment(FILE *fd, entity m, bool is_fortran)
Definition: declarations.c:297

References fprint_any_environment().

Referenced by ResetCurrentCompilationUnitEntity(), and ResetCurrentModule().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ fprint_environment()

void fprint_environment ( FILE *  fd,
entity  m 
)
Parameters
fdd

Definition at line 287 of file declarations.c.

288 {
289  fprint_any_environment(fd, m, true);
290 }

References fprint_any_environment().

Referenced by EndOfProcedure(), make_array_communication_module(), make_scalar_communication_module(), make_start_ru_module(), make_wait_ru_module(), ProcessEntry(), and store_new_module().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ fprint_functional()

void fprint_functional ( FILE *  fd,
functional  f 
)

This function is called from c_parse() via ResetCurrentModule() and fprint_environment()

(void) fprintf(fd, " %s:", type_to_string(ta));

Well, seems to occur for C compilation units, instead of void...

An argument can be functional, but not (yet) a result.

Parameters
fdd

Definition at line 227 of file declarations.c.

228 {
229  type tr = functional_result(f);
230  int count = 0;
231 
233  type ta = parameter_type(p);
234 
235  pips_assert("Argument type is variable or varags:variable or functional or void",
236  type_variable_p(ta)
238  || type_functional_p(ta)
239  || type_void_p(ta));
240 
241  if(count>0)
242  (void) fprintf(fd, " x ");
243  count++;
244 
245  if(type_functional_p(ta)) {
246  functional fa = type_functional(ta);
247  /* (void) fprintf(fd, " %s:", type_to_string(ta)); */
248  (void) fprintf(fd, "(");
249  fprint_functional(fd, fa);
250  (void) fprintf(fd, ")");
251  }
252  else if(type_void_p(ta)) {
253  (void) fprintf(fd, "(");
254  (void) fprintf(fd, ")");
255  }
256  else {
257  if(type_varargs_p(ta)) {
258  (void) fprintf(fd, " %s:", type_to_string(ta));
259  ta = type_varargs(ta);
260  }
261  (void) fprintf(fd, "%s", basic_to_string(variable_basic(type_variable(ta))));
262  }
263  }
264 
266  (void) fprintf(fd, " ()");
267  }
268  (void) fprintf(fd, " -> ");
269 
270  if(type_variable_p(tr))
271  (void) fprintf(fd, " %s\n", basic_to_string(variable_basic(type_variable(tr))));
272  else if(type_void_p(tr))
273  (void) fprintf(fd, " %s\n", type_to_string(tr));
274  else if(type_unknown_p(tr)){
275  /* Well, seems to occur for C compilation units, instead of void... */
276  (void) fprintf(fd, " %s\n", type_to_string(tr));
277  }
278  else if(type_varargs_p(tr)) {
279  (void) fprintf(fd, " %s:%s", type_to_string(tr),
281  }
282  else
283  /* An argument can be functional, but not (yet) a result. */
284  pips_internal_error("Ill. type %d", type_tag(tr));
285 }
static int count
Definition: SDG.c:519
#define PARAMETER(x)
PARAMETER.
Definition: ri.h:1788

References basic_to_string(), count, ENDP, f(), FOREACH, fprintf(), functional_parameters, functional_result, PARAMETER, parameter_type, pips_assert, pips_internal_error, type_functional, type_functional_p, type_tag, type_to_string(), type_unknown_p, type_varargs, type_varargs_p, type_variable, type_variable_p, type_void_p, and variable_basic.

Referenced by DeclareVariable(), fprint_any_environment(), and UpdateFunctionalType().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ get_common_members()

list get_common_members ( entity  common,
entity __attribute__((unused))  module,
bool __attribute__((unused))  only_primary 
)

The fprint_functional() and fprint_environment() functions are moved from syntax/declaration.c.

C Version of print_common_layout this is called by fprint_environment(). This function is much simpler than Fortran Version

Definition at line 106 of file declarations.c.

109 {
110  list result = NIL;
111  //int cumulated_offset = 0;
112  pips_assert("entity is a common", type_area_p(entity_type(common)));
113 
114  list ld = area_layout(type_area(entity_type(common)));
116 
117  for(; !ENDP(ld); ld = CDR(ld))
118  {
119  v = ENTITY(CAR(ld));
120  storage s = entity_storage(v);
121  if(storage_ram_p(s))
122  {
123  result = CONS(ENTITY, v, result);
124  }
125  }
126  return gen_nreverse(result);
127 }
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
#define storage_ram_p(x)
Definition: ri.h:2519
#define area_layout(x)
Definition: ri.h:546

References area_layout, CAR, CDR, CONS, ENDP, ENTITY, entity_storage, entity_type, entity_undefined, gen_nreverse(), NIL, pips_assert, storage_ram_p, type_area, and type_area_p.

Referenced by dump_common_layout(), and print_C_common_layout().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ print_C_common_layout()

void print_C_common_layout ( FILE *  fd,
entity  c,
bool  debug_p 
)

Look for variables aliased with a variable in this common

Parameters
fdd
debug_pebug_p

Definition at line 129 of file declarations.c.

130 {
132  list members = get_common_members(c, mod, false);
133  list equiv_members = NIL;
134 
135  (void) fprintf(fd, "\nLayout for memory area \"%s\" of size %td: \n",
137 
138  if(ENDP(members)) {
139  pips_assert("An empty area has size 0", area_size(type_area(entity_type(c))) ==0);
140  (void) fprintf(fd, "\t* empty area *\n\n");
141  }
142  else {
143  if(area_size(type_area(entity_type(c))) == 0)
144  {
145  if(debug_p) {
146  user_warning("print_common_layout","Non-empty area %s should have a final size greater than 0\n",
147  entity_module_name(c));
148  }
149  else {
150  // The non-empty area can have size zero if the entity is extern
151  //pips_internal_error(// "Non-empty area %s should have a size greater than 0",
152  // entity_module_name(c));
153  }
154  }
155  MAP(ENTITY, m,
156  {
157  pips_assert("RAM storage",
159  int s;
160  // There can be a Array whose size is not known (Dynamic Variables)
161  SizeOfArray(m, &s);
162 
163  pips_assert("An area has no offset as -1",
166  (void) fprintf(fd,
167  "\tDynamic Variable %s, \toffset = UNKNOWN, \tsize = DYNAMIC\n",
168  entity_name(m));
169  }
171 
172  (void) fprintf(fd,
173  "\tExternal Variable %s,\toffset = UNKNOWN,\tsize = %d\n",
174  entity_name(m),s);
175  }
176  else {
177  (void) fprintf(fd,
178  "\tVariable %s,\toffset = %td,\tsize = %d\n",
179  entity_name(m),
181  s);
182  }
183  //}
184  },
185  members);
186  (void) fprintf(fd, "\n");
187  /* Look for variables aliased with a variable in this common */
188  MAP(ENTITY, m,
189  {
191 
192  equiv_members = arguments_union(equiv_members, equiv);
193  },
194  members);
195 
196  if(!ENDP(equiv_members)){
197 
198  equiv_members = arguments_difference(equiv_members, members);
199  if(!ENDP(equiv_members)) {
200  sort_list_of_entities(equiv_members);
201 
202  (void) fprintf(fd, "\tVariables aliased to this common:\n");
203 
204  MAP(ENTITY, m,
205  {
206  int asize;
207  pips_assert("RAM storage", storage_ram_p(entity_storage(m)));
208  if (!SizeOfArray(m, &asize))
209  asize = -1;
210  (void) fprintf(fd,
211  "\tVariable %s,\toffset = %td,\tsize = %d\n",
212  entity_name(m),
214  asize);
215  },
216  equiv_members);
217  (void) fprintf(fd, "\n");
218  gen_free_list(equiv_members);
219  }
220  }
221  }
222  gen_free_list(members);
223 }
cons * arguments_union(cons *a1, cons *a2)
cons * arguments_union(cons * a1, cons * a2): returns a = union(a1, a2) where a1 and a2 are lists of ...
Definition: arguments.c:116
cons * arguments_difference(cons *a1, cons *a2)
set difference: a1 - a2 ; similar to set intersection
Definition: arguments.c:233
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
#define user_warning(fn,...)
Definition: misc-local.h:262
#define DYNAMIC_RAM_OFFSET
FI: I would have assumed that it is used for the stack area, but I must be wrong.....
#define UNDEFINED_RAM_OFFSET
list get_common_members(entity common, entity __attribute__((unused)) module, bool __attribute__((unused)) only_primary)
The fprint_functional() and fprint_environment() functions are moved from syntax/declaration....
Definition: declarations.c:106
void sort_list_of_entities(list l)
sorted in place.
Definition: entity.c:1358
const char * entity_module_name(entity e)
See comments about module_name().
Definition: entity.c:1092
#define storage_ram(x)
Definition: ri.h:2521
#define ram_shared(x)
Definition: ri.h:2253
#define ram_offset(x)
Definition: ri.h:2251

References area_size, arguments_difference(), arguments_union(), DYNAMIC_RAM_OFFSET, ENDP, ENTITY, entity_module_name(), entity_name, entity_storage, entity_type, fprintf(), gen_free_list(), get_common_members(), get_current_module_entity(), MAP, NIL, pips_assert, ram_offset, ram_shared, SizeOfArray(), sort_list_of_entities(), storage_ram, storage_ram_p, type_area, UNDEFINED_RAM_OFFSET, and user_warning.

Referenced by fprint_any_environment().

+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ split_initializations_in_statement()

void split_initializations_in_statement ( statement  s)

Transform a declaration with an initialization statement into 2 parts, a declaration statement and an initializer statement.

gen_recurse callback on exiting statements. For a declaration to be split:

  • it must be a local declaration
  • the initial value, if any, must be a valid rhs expression or an array initialization; struct initialization are not (yet) supported

generate C99 code

The initialization of a static variable cannot be split

if this transformation led to an uninitialized const, remove the const qualifier

This is not very smart... You do not need pcs in C99 since you are going to add the assignment statements just after the current declaration statement...

Chain the new list within the current statement list

Move to the next original element nsl

Move to the next statement

Move to the next statement

generate C89 code

Do nothing ?

Definition at line 437 of file declarations.c.

438 {
439  if(!get_bool_property("C89_CODE_GENERATION") && statement_block_p(s)) {
440  /* generate C99 code */
441  list cs = list_undefined;
442  list pcs = NIL;
443  list nsl = statement_block(s); // new statement list
444  for( cs = statement_block(s); !ENDP(cs); ) {
445  statement ls = STATEMENT(CAR(cs));
446  if(declaration_statement_p(ls)) {
447  list inits = NIL;
448  list decls = statement_declarations(ls); // Non-recursive
449  //statement sc = statement_undefined; // statement copy
450 
451  FOREACH(ENTITY, var, decls) {
452  /* The initialization of a static variable cannot be split */
453  if(entity_static_variable_p(var)) {
454  pips_user_warning("Initialization of variable \"%s\" cannot be "
455  "split from its declaration because \"%s\" "
456  "is a static variable.\n",
458  }
459  else {
460  const char* mn = entity_module_name(var);
461  const char* cmn = get_current_module_name();
462  if ( same_string_p(mn,cmn)
464  ) {
466  if (expression_is_C_rhs_p(ie)) {
468  inits = gen_nconc(inits, CONS(statement, is, NIL));
470  }
471  else if(entity_array_p(var)) {
472  inits = gen_nconc(inits, brace_expression_to_statements(var,ie));
475  }
477  inits = gen_nconc(inits, brace_expression_to_statements(var,ie));
479  }
480  else {
481  pips_user_warning("split initializations not implemented yet for structures\n");
482  }
483  /* if this transformation led to an uninitialized const, remove the const qualifier */
484  if(value_unknown_p(entity_initial(var))) {
485  list tmp = gen_copy_seq(entity_qualifiers(var));
486  FOREACH(QUALIFIER,q,tmp) {
487  if(qualifier_const_p(q))
489  }
490  gen_free_list(tmp);
491  }
492  }
493  }
494  }
495 
496  if(!ENDP(inits)) {
497  /* This is not very smart... You do not need pcs in C99
498  since you are going to add the assignment statements
499  just after the current declaration statement... */
500  inits = CONS(STATEMENT, ls, inits);
501  /* Chain the new list within the current statement list */
502  if(ENDP(pcs)) {
503  nsl = inits;
504  }
505  else {
506  CDR(pcs) = inits;
507  }
508  /* Move to the next original element nsl */
509  pcs = gen_last(inits);
510  CDR(pcs) = CDR(cs);
511  POP(cs);
512  }
513  else {
514  /* Move to the next statement */
515  pcs = cs;
516  POP(cs);
517  }
518  }
519  else {
520  /* Move to the next statement */
521  pcs = cs;
522  POP(cs);
523  }
524  }
526  }
527  else if(statement_block_p(s)) {
528  /* generate C89 code */
529  list cs = list_undefined;
530  //list pcs = NIL;
531  //list nsl = statement_block(s); // new statement list
532  list inits = NIL; // list of initialization statements
533 
534  for( cs = statement_block(s); !ENDP(cs); POP(cs)) {
535  statement ls = STATEMENT(CAR(cs));
536  if(declaration_statement_p(ls)) {
537  list decls = statement_declarations(ls); // Non-recursive
538  //statement sc = statement_undefined; // statement copy
539 
540  FOREACH(ENTITY, var, decls) {
541  const char* mn = entity_module_name(var);
542  const char* cmn = get_current_module_name();
543  if ( strcmp(mn,cmn) == 0
545  ) {
547  if(expression_undefined_p(ie)) {}
548  else if (expression_is_C_rhs_p(ie)) {
550  inits = gen_nconc(inits, CONS(statement, is, NIL));
552  }
553  else if(entity_array_p(var)) {
554  inits=gen_nconc(inits,brace_expression_to_statements(var,ie));
556  }
557  else {
558  pips_user_warning("split initializations not implemented yet for structures\n");
559  }
560  }
561  }
562  }
563 
564  if(!ENDP(inits)) {
565  list ncs = CDR(cs);
566  if(ENDP(ncs) || !declaration_statement_p(STATEMENT(CAR(ncs)))) {
567  list pcs = gen_last(inits);
568  CDR(cs) = inits;
569  CDR(pcs) = ncs;
570  break;
571  }
572  }
573  }
574  //instruction_block(statement_instruction(s)) = nsl;
575  }
576  else {
577  /* Do nothing ? */
578  }
579 }
value make_value_unknown(void)
Definition: ri.c:2847
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
const char * get_current_module_name(void)
Get the name of the current module.
Definition: static.c:121
void gen_remove_once(list *pl, const void *o)
Remove the first occurence of o in list pl:
Definition: list.c:691
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
list gen_last(list l)
Return the last element of a list.
Definition: list.c:578
list statement_block(statement)
Get the list of block statements of a statement sequence.
Definition: statement.c:1338
statement make_assign_statement(expression, expression)
Definition: statement.c:583
bool declaration_statement_p(statement)
Had to be optimized according to Beatrice Creusillet.
Definition: statement.c:224
#define same_string_p(s1, s2)
#define statement_block_p(stat)
#define instruction_block(i)
bool entity_array_p(entity e)
Is e a variable with an array type?
Definition: entity.c:754
list entity_qualifiers(entity e)
return the qualifiers associated to entity e if it's a variable NIL otherwise
Definition: entity.c:1394
bool expression_is_C_rhs_p(expression exp)
Not all expressions can be used as right-hand side (rhs) in C assignments.
Definition: expression.c:2582
void brace_expression_to_updated_type(entity arr, expression e)
use a brace expression to update the type of array "arr" if the dimensions are implicit
Definition: expression.c:3517
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
list brace_expression_to_statements(entity arr, expression e)
converts a brace expression used to initialize an array (not a struct yet) into a statement sequence
Definition: expression.c:3480
bool entity_static_variable_p(entity)
return true if the entity is declared with the keyword static
Definition: variable.c:1146
type entity_basic_concrete_type(entity)
retrieves or computes and then returns the basic concrete type of an entity
Definition: type.c:3677
expression variable_initial_expression(entity)
Returns a copy of the initial (i.e.
Definition: variable.c:1899
bool struct_type_p(type)
Returns true if t is of type derived and if the derived type is a struct.
Definition: type.c:3121
#define qualifier_const_p(x)
Definition: ri.h:2176
#define QUALIFIER(x)
QUALIFIER.
Definition: ri.h:2106
#define value_unknown_p(x)
Definition: ri.h:3077
#define variable_qualifiers(x)
Definition: ri.h:3124
#define expression_undefined_p(x)
Definition: ri.h:1224
#define statement_declarations(x)
Definition: ri.h:2460
#define statement_instruction(x)
Definition: ri.h:2458
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413

References brace_expression_to_statements(), brace_expression_to_updated_type(), CAR, CDR, CONS, declaration_statement_p(), ENDP, ENTITY, entity_array_p(), entity_basic_concrete_type(), entity_initial, entity_module_name(), entity_qualifiers(), entity_static_variable_p(), entity_to_expression(), entity_type, entity_user_name(), expression_is_C_rhs_p(), expression_undefined_p, FOREACH, gen_copy_seq(), gen_free_list(), gen_last(), gen_nconc(), gen_remove_once(), get_bool_property(), get_current_module_name(), instruction_block, list_undefined, make_assign_statement(), make_value_unknown(), NIL, pips_user_warning, POP, QUALIFIER, qualifier_const_p, same_string_p, STATEMENT, statement_block(), statement_block_p, statement_declarations, statement_instruction, struct_type_p(), type_variable, value_unknown_p, variable_initial_expression(), and variable_qualifiers.

Referenced by MakeForloopWithIndexDeclaration(), and statement_split_initializations().

+ Here is the call graph for this function:
+ Here is the caller graph for this function: