PIPS
communication_generation.c File Reference
#include <stdio.h>
#include <ctype.h>
#include <string.h>
#include "boolean.h"
#include <stdbool.h>
#include <limits.h>
#include "genC.h"
#include "linear.h"
#include "ri.h"
#include "effects.h"
#include "database.h"
#include "misc.h"
#include "text.h"
#include "text-util.h"
#include "ri-util.h"
#include "workspace-util.h"
#include "effects-util.h"
#include "accel-util.h"
#include "effects-generic.h"
#include "effects-simple.h"
#include "pipsdbm.h"
#include "resources.h"
#include "control.h"
#include "conversion.h"
#include "properties.h"
#include "semantics.h"
#include "transformations.h"
#include "c_syntax.h"
#include "effects-convex.h"
#include "complexity_ri.h"
#include "complexity.h"
#include "dg.h"
#include "graph.h"
#include "ricedg.h"
#include "chains.h"
#include "regions_to_loops.h"
#include "task_parallelization.h"
+ Include dependency graph for communication_generation.c:

Go to the source code of this file.

Macros

#define SUCCESSORS   true
 
#define PREDECESSORS   false
 

Typedefs

typedef dg_arc_label arc_label
 Instantiation of the dependence graph: More...
 
typedef dg_vertex_label vertex_label
 

Functions

statement make_com_loopbody (entity v, bool neighbor, list vl, int k)
 
static statement Psysteme_to_loop_nest (entity v, list vl, Pbase b, Psysteme p, bool neighbor, list l_var, int k)
 
statement region_to_com_nest (region r, bool isRead, int k)
 Returns the entity corresponding to the global name. More...
 
static void replace_indices_region_com (region r, list *dadd, int indNum, entity module)
 This function is in charge of replacing the PHI entity of the region by generated indices. More...
 
static statement com_call (bool neighbor, list args_com, int k)
 
static list transfer_regions (statement parent, statement child)
 
static list hierarchical_com (statement s, bool neighbor, int kp)
 
static list successors (list l)
 
static list gen_send_communications (statement s, vertex tau, persistant_statement_to_cluster st_to_cluster, int kp)
 
static list predecessors (statement st, graph tg)
 
static list gen_recv_communications (statement sv, persistant_statement_to_cluster st_to_cluster, graph tg, int kp)
 
void communications_construction (graph tg, statement stmt, persistant_statement_to_cluster st_to_cluster, int kp)
 

Macro Definition Documentation

◆ PREDECESSORS

#define PREDECESSORS   false

Definition at line 53 of file communication_generation.c.

◆ SUCCESSORS

#define SUCCESSORS   true

Definition at line 52 of file communication_generation.c.

Typedef Documentation

◆ arc_label

Instantiation of the dependence graph:

Definition at line 44 of file communication_generation.c.

◆ vertex_label

Definition at line 45 of file communication_generation.c.

Function Documentation

◆ com_call()

static statement com_call ( bool  neighbor,
list  args_com,
int  k 
)
static

Definition at line 164 of file communication_generation.c.

165 {
166  list declarations = NIL;
167  list sl = NIL;
168  int indNum = 0;
170  if(gen_length(args_com)>0){
171  FOREACH(effect, reg, args_com){
172  entity e = region_entity(reg);
173  if(!io_entity_p(e) && !stdin_entity_p(e)){
174  list phi = NIL;
176  statement s = region_to_com_nest(reg, neighbor, k);
177  if(!statement_undefined_p(s)){
178  sl = CONS(STATEMENT, s, sl);
179  indNum++;
180  declarations = gen_nconc(declarations, phi);
181  }
182  }
183  }
185  if(gen_length(sl) > 0)
186  s_com = make_block_statement(sl);
187  }
188  return s_com;
189 }
statement region_to_com_nest(region r, bool isRead, int k)
Returns the entity corresponding to the global name.
static void replace_indices_region_com(region r, list *dadd, int indNum, entity module)
This function is in charge of replacing the PHI entity of the region by generated indices.
#define region_entity(reg)
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
size_t gen_length(const list l)
Definition: list.c:150
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
statement make_continue_statement(entity)
Definition: statement.c:953
entity entity_empty_label(void)
Definition: entity.c:1105
bool io_entity_p(entity e)
Several implicit entities are declared to define the implicit effects of IO statements.
Definition: entity.c:1139
bool stdin_entity_p(entity e)
Definition: entity.c:1203
#define statement_undefined_p(x)
Definition: ri.h:2420
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
list com_declarations_to_add
spire_generation.c
The structure used to build lists in NewGen.
Definition: newgen_list.h:41

References com_declarations_to_add, CONS, entity_empty_label(), FOREACH, gen_length(), gen_nconc(), get_current_module_entity(), io_entity_p(), make_block_statement(), make_continue_statement(), NIL, region_entity, region_to_com_nest(), replace_indices_region_com(), STATEMENT, statement_undefined_p, and stdin_entity_p().

Referenced by communications_construction(), gen_mpi_send_recv(), gen_recv_communications(), gen_send_communications(), and hierarchical_com().

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

◆ communications_construction()

void communications_construction ( graph  tg,
statement  stmt,
persistant_statement_to_cluster  st_to_cluster,
int  kp 
)
Parameters
tgg
stmttmt
st_to_clustert_to_cluster
kpp

Definition at line 337 of file communication_generation.c.

338 {
342  switch(instruction_tag(inst)){
343  case is_instruction_block:{
344  list vertices = graph_vertices(tg), coms_send = NIL, coms_recv = NIL, coms_st = NIL;
345  list barrier = NIL;
346  MAPL(stmt_ptr,
347  {
348  statement ss = STATEMENT(CAR(stmt_ptr ));
349  if(statement_block_p(ss)){
351  MAPL(sb_ptr,
352  {
353  statement sb = STATEMENT(CAR(sb_ptr ));
354  if(statement_block_p(sb)){
356  MAPL(ss_ptr,
357  {
358  statement s = STATEMENT(CAR(ss_ptr ));
359  barrier = CONS(STATEMENT,s,barrier);
360  },
361  instruction_block(sbinst));
362  }
363  else
364  barrier = CONS(STATEMENT,sb,barrier);
365  },
366  instruction_block(sinst));
367  }
368  else
369  barrier = CONS(STATEMENT,ss,barrier);
370  },
371  instruction_block(inst));
372  FOREACH(STATEMENT, s, barrier)
373  {
374  bool found_p = false;
375  FOREACH(VERTEX, pre, vertices) {
376  statement this = vertex_to_statement(pre);
378  found_p = true;
379  break;
380  }
381  }
382  if(found_p){
383  int ki = apply_persistant_statement_to_cluster(st_to_cluster, statement_ordering(s));
384  list args_send = gen_recv_communications(s, st_to_cluster, tg, kp);
385  list args_recv = gen_send_communications(s, statement_to_vertex(s,tg), st_to_cluster, kp);
386  if(gen_length(args_recv) > 0 && (kp != ki) )
387  coms_recv = CONS(STATEMENT, com_call(PREDECESSORS, args_recv, ki), coms_recv);
388  if(gen_length(args_send) > 0 && (kp != ki) )
389  coms_send = CONS(STATEMENT, com_call(SUCCESSORS, args_send, ki), coms_send);
390  communications_construction(tg, s, st_to_cluster, ki);
391  }
392  else
393  communications_construction(tg, s, st_to_cluster, kp);
394  }
395  if((gen_length(coms_send) > 0 || gen_length(coms_recv) > 0) && (kp != -1)){
396  statement new_s = make_statement(
403  if(gen_length(coms_recv) > 0){
404  FOREACH(STATEMENT, st, coms_recv){
405  coms_st = CONS(STATEMENT, st, coms_st);
406  }
407  }
408  coms_st = CONS(STATEMENT, new_s, coms_st);
409  if(gen_length(coms_send) > 0){
410  FOREACH(STATEMENT, st, coms_send){
411  coms_st = CONS(STATEMENT, st, coms_st);
412  }
413  }
419  }
420  break;
421  }
422  case is_instruction_test:{
423  test t = instruction_test(inst);
424  communications_construction(tg, test_true(t), st_to_cluster, kp);
425  communications_construction(tg, test_false(t), st_to_cluster, kp);
426  break;
427  }
428  case is_instruction_loop :{
429  loop l = statement_loop(stmt);
430  statement body = loop_body(l);
431  communications_construction(tg, body, st_to_cluster, kp);
432  break;
433  }
434  default:
435  break;
436  }
437  }
438  return;
439 }
statement make_statement(entity a1, intptr_t a2, intptr_t a3, string a4, instruction a5, list a6, string a7, extensions a8, synchronization a9)
Definition: ri.c:2222
instruction make_instruction_sequence(sequence _field_)
Definition: ri.c:1169
bool bound_persistant_statement_to_cluster_p(persistant_statement_to_cluster f, intptr_t k)
Definition: ri.c:1552
intptr_t apply_persistant_statement_to_cluster(persistant_statement_to_cluster f, intptr_t k)
Definition: ri.c:1540
synchronization make_synchronization_none(void)
Definition: ri.c:2424
sequence make_sequence(list a)
Definition: ri.c:2125
#define SUCCESSORS
static statement com_call(bool neighbor, list args_com, int k)
#define PREDECESSORS
static list gen_send_communications(statement s, vertex tau, persistant_statement_to_cluster st_to_cluster, int kp)
static list gen_recv_communications(statement sv, persistant_statement_to_cluster st_to_cluster, graph tg, int kp)
void communications_construction(graph tg, statement stmt, persistant_statement_to_cluster st_to_cluster, int kp)
int gen_consistent_p(gen_chunk *obj)
GEN_CONSISTENT_P dynamically checks the type correctness of OBJ.
Definition: genClib.c:2398
#define graph_vertices(x)
Definition: graph.h:82
#define VERTEX(x)
VERTEX.
Definition: graph.h:122
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
#define MAPL(_map_list_cp, _code, _l)
Apply some code on the addresses of all the elements of a list.
Definition: newgen_list.h:203
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
statement vertex_to_statement(vertex v)
Vertex_to_statement looks for the statement that is pointed to by vertex v.
Definition: util.c:45
static vertex statement_to_vertex(statement s, graph g)
Definition: impact_check.c:227
#define STATEMENT_ORDERING_UNDEFINED
mapping.h inclusion
Definition: newgen-local.h:35
static bool statement_equal_p(statement s1, statement s2)
Definition: unstructured.c:55
#define statement_block_p(stat)
#define STATEMENT_NUMBER_UNDEFINED
default values
#define is_instruction_block
soft block->sequence transition
#define instruction_block(i)
#define empty_comments
Empty comments (i.e.
extensions empty_extensions(void)
extension.c
Definition: extension.c:43
#define loop_body(x)
Definition: ri.h:1644
#define statement_ordering(x)
Definition: ri.h:2454
#define test_false(x)
Definition: ri.h:2837
#define statement_synchronization(x)
Definition: ri.h:2466
#define statement_label(x)
Definition: ri.h:2450
@ is_instruction_test
Definition: ri.h:1470
@ is_instruction_loop
Definition: ri.h:1471
#define instruction_tag(x)
Definition: ri.h:1511
#define test_true(x)
Definition: ri.h:2835
#define statement_extensions(x)
Definition: ri.h:2464
#define statement_instruction(x)
Definition: ri.h:2458
#define statement_comments(x)
Definition: ri.h:2456
#define instruction_test(x)
Definition: ri.h:1517
Definition: statement.c:4047
Definition: statement.c:54
A gen_chunk is used to store every object.
Definition: genC.h:58

References apply_persistant_statement_to_cluster(), bound_persistant_statement_to_cluster_p(), CAR, com_call(), CONS, empty_comments, empty_extensions(), FOREACH, gen_consistent_p(), gen_length(), gen_recv_communications(), gen_send_communications(), graph_vertices, instruction_block, instruction_tag, instruction_test, is_instruction_block, is_instruction_loop, is_instruction_test, loop_body, make_instruction_sequence(), make_sequence(), make_statement(), make_synchronization_none(), MAPL, NIL, PREDECESSORS, STATEMENT, statement_block_p, statement_comments, statement_equal_p(), statement_extensions, statement_instruction, statement_label, statement_loop(), STATEMENT_NUMBER_UNDEFINED, statement_ordering, STATEMENT_ORDERING_UNDEFINED, statement_synchronization, statement_to_vertex(), SUCCESSORS, test_false, test_true, VERTEX, and vertex_to_statement().

Referenced by spire_distributed_unstructured_to_structured().

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

◆ gen_recv_communications()

static list gen_recv_communications ( statement  sv,
persistant_statement_to_cluster  st_to_cluster,
graph  tg,
int  kp 
)
static

Definition at line 297 of file communication_generation.c.

298 {
299  int i;
300  //list args_recv, list_st = NIL, h_args_com = NIL;
301  list list_st = NIL, h_args_com = NIL;
302  statement new_s = make_statement(
303  statement_label(sv),
306  statement_comments(sv),
309  list_st = CONS(STATEMENT, new_s, NIL);
310  for(i = 0; i < NBCLUSTERS; i++){
311  //args_recv = NIL;
312  list preds = predecessors(sv, tg);
313  FOREACH(STATEMENT, parent, preds){
314  if(bound_persistant_statement_to_cluster_p(st_to_cluster, statement_ordering(parent))) {
316  list com_regions = transfer_regions(parent, sv);
317  if(gen_length(com_regions)>0){
318  list_st = CONS(STATEMENT, com_call(PREDECESSORS, com_regions, i), list_st);
319  }
320  }
321  }
322  }
323  }
324  if(gen_length(list_st) > 1){
325  instruction ins_seq = make_instruction_sequence(make_sequence((list_st)));//make_statement_list(new_s, st_send)));
326  statement_instruction(sv) = ins_seq;
330  }
331  if(apply_persistant_statement_to_cluster(st_to_cluster, statement_ordering(sv)) != kp && (kp != -1))
332  h_args_com = hierarchical_com(sv, PREDECESSORS, kp);
333  return h_args_com;
334 }
int NBCLUSTERS
parameters of BDSC, to be recovered using pips properties
Definition: SDG.c:57
static list hierarchical_com(statement s, bool neighbor, int kp)
static list predecessors(statement st, graph tg)
static list transfer_regions(statement parent, statement child)

References apply_persistant_statement_to_cluster(), bound_persistant_statement_to_cluster_p(), com_call(), CONS, empty_comments, empty_extensions(), FOREACH, gen_length(), hierarchical_com(), make_instruction_sequence(), make_sequence(), make_statement(), make_synchronization_none(), NBCLUSTERS, NIL, PREDECESSORS, predecessors(), STATEMENT, statement_comments, statement_extensions, statement_instruction, statement_label, STATEMENT_NUMBER_UNDEFINED, statement_ordering, STATEMENT_ORDERING_UNDEFINED, statement_synchronization, and transfer_regions().

Referenced by communications_construction().

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

◆ gen_send_communications()

static list gen_send_communications ( statement  s,
vertex  tau,
persistant_statement_to_cluster  st_to_cluster,
int  kp 
)
static

Definition at line 240 of file communication_generation.c.

241 {
242  int i;
243  //list args_send, list_st = NIL, h_args_com = NIL;
244  list list_st = NIL, h_args_com = NIL;
245  statement new_s = make_statement(
246  statement_label(s),
252  list_st = CONS(STATEMENT, new_s, NIL);
253  for(i = 0; i < NBCLUSTERS; i++){
254  //args_send = NIL;
259  &&
261  list com_regions = transfer_regions(s, ss);
262  if(gen_length(com_regions)>0){
263  list_st = CONS(STATEMENT, com_call(SUCCESSORS, com_regions, i),list_st);
264  }
265  }
266  }
267  }
268  }
269  if(gen_length(list_st) > 1){
271  statement_instruction(s) = ins_seq;
275  }
276  if(apply_persistant_statement_to_cluster(st_to_cluster, statement_ordering(s)) != kp && (kp != -1))
277  h_args_com = hierarchical_com(s, SUCCESSORS, kp);
278  return h_args_com;
279 }
static list successors(list l)
#define vertex_successors(x)
Definition: graph.h:154
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304

References apply_persistant_statement_to_cluster(), bound_persistant_statement_to_cluster_p(), com_call(), CONS, empty_comments, empty_extensions(), FOREACH, gen_length(), gen_nreverse(), hierarchical_com(), make_instruction_sequence(), make_sequence(), make_statement(), make_synchronization_none(), NBCLUSTERS, NIL, STATEMENT, statement_comments, statement_extensions, statement_instruction, statement_label, STATEMENT_NUMBER_UNDEFINED, statement_ordering, STATEMENT_ORDERING_UNDEFINED, statement_synchronization, SUCCESSORS, successors(), transfer_regions(), and vertex_successors.

Referenced by communications_construction().

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

◆ hierarchical_com()

static list hierarchical_com ( statement  s,
bool  neighbor,
int  kp 
)
static

Definition at line 199 of file communication_generation.c.

200 {
201  list h_sequence = NIL;
203  if(gen_length(h_regions_com)>0){
204  statement new_s = make_statement(
205  statement_label(s),
211  statement com = com_call(neighbor, h_regions_com, kp);
212  if(!neighbor)
213  h_sequence = CONS(STATEMENT,com,h_sequence);
214  h_sequence = CONS(STATEMENT,new_s,h_sequence);
215  if(neighbor)
216  h_sequence = CONS(STATEMENT,com,h_sequence);
217  if(gen_length(h_sequence) > 1){
219  statement_instruction(s) = ins_seq;
223  }
224  }
225  return h_regions_com;
226 }
list regions_dup(list)
list load_statement_out_regions(statement)
list load_statement_in_regions(statement)

References com_call(), CONS, empty_comments, empty_extensions(), gen_length(), gen_nreverse(), load_statement_in_regions(), load_statement_out_regions(), make_instruction_sequence(), make_sequence(), make_statement(), make_synchronization_none(), NIL, regions_dup(), STATEMENT, statement_comments, statement_extensions, statement_instruction, statement_label, STATEMENT_NUMBER_UNDEFINED, STATEMENT_ORDERING_UNDEFINED, and statement_synchronization.

Referenced by gen_recv_communications(), and gen_send_communications().

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

◆ make_com_loopbody()

statement make_com_loopbody ( entity  v,
bool  neighbor,
list  vl,
int  k 
)

Definition at line 55 of file communication_generation.c.

55  {
56  entity new_ent = make_constant_entity(i2a(k), is_basic_int, 4);
59  list args_com = CONS(EXPRESSION, e, CONS(EXPRESSION, exp, NIL));
60  string com = (neighbor) ? SEND_FUNCTION_NAME : RECV_FUNCTION_NAME;
62  gen_nreverse(args_com),
65  pips_assert("communication body is not properly generated", statement_consistent_p(s));
66  return s;
67 }
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
bool statement_consistent_p(statement p)
Definition: ri.c:2195
entity make_constant_entity(string name, tag bt, size_t size)
For historical reason, call the Fortran version.
Definition: constant.c:301
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535
statement make_call_statement(string, list, entity, string)
This function is limited to intrinsics calls...
Definition: statement.c:1274
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
char * i2a(int)
I2A (Integer TO Ascii) yields a string for a given Integer.
Definition: string.c:121
#define RECV_FUNCTION_NAME
#define SEND_FUNCTION_NAME
SPIRE API.
expression reference_to_expression(reference r)
Definition: expression.c:196
expression make_entity_expression(entity e, cons *inds)
Definition: expression.c:176
@ is_basic_int
Definition: ri.h:571
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined
Definition: ri.h:2761
#define exp
Avoid some warnings from "gcc -Wshadow".
Definition: vasnprintf.c:207

References CONS, empty_comments, entity_undefined, exp, EXPRESSION, gen_full_copy_list(), gen_nreverse(), i2a(), is_basic_int, make_call_statement(), make_constant_entity(), make_entity_expression(), make_reference(), NIL, pips_assert, RECV_FUNCTION_NAME, reference_to_expression(), SEND_FUNCTION_NAME, and statement_consistent_p().

Referenced by Psysteme_to_loop_nest().

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

◆ predecessors()

static list predecessors ( statement  st,
graph  tg 
)
static

Definition at line 281 of file communication_generation.c.

282 {
283  list vertices = graph_vertices(tg);
284  list preds = NIL;
285  FOREACH(VERTEX, v, vertices) {
286  statement parent = vertex_to_statement(v);
287  FOREACH(SUCCESSOR, su, (vertex_successors(v))) {
288  vertex s = successor_vertex(su);
289  statement child = vertex_to_statement(s);
290  if(statement_equal_p(child, st) && gen_occurences(parent, preds) == 0)
291  preds = CONS(STATEMENT, parent, preds);
292  }
293  }
294  return preds;
295 }
#define successor_vertex(x)
Definition: graph.h:118
#define SUCCESSOR(x)
SUCCESSOR.
Definition: graph.h:86
int gen_occurences(const void *vo, const list l)
count occurences of vo in l
Definition: list.c:746

References CONS, FOREACH, gen_occurences(), graph_vertices, NIL, STATEMENT, statement_equal_p(), SUCCESSOR, successor_vertex, VERTEX, vertex_successors, and vertex_to_statement().

Referenced by debug_unstructured(), gen_recv_communications(), reduce_sequence(), and replace_control_with_unstructured().

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

◆ Psysteme_to_loop_nest()

static statement Psysteme_to_loop_nest ( entity  v,
list  vl,
Pbase  b,
Psysteme  p,
bool  neighbor,
list  l_var,
int  k 
)
static

Definition at line 69 of file communication_generation.c.

69  {
70  Psysteme condition, enumeration;
71  statement body = make_com_loopbody(v, neighbor, l_var, k);;
72  algorithm_row_echelon_generic(p, b, &condition, &enumeration, true);
74  pips_assert("s is not properly generated (systeme_to_loop_nest)", statement_consistent_p(s));
75  return s;
76 }
statement make_com_loopbody(entity v, bool neighbor, list vl, int k)
statement systeme_to_loop_nest(Psysteme, list, statement, entity)
sc is used to generate the loop nest bounds for variables vars.
#define DIVIDE_OPERATOR_NAME
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
void algorithm_row_echelon_generic(Psysteme scn, Pbase base_index, Psysteme *pcondition, Psysteme *penumeration, bool redundancy)
each variable should be at least within one <= and one >=; scn IS NOT modified.

References algorithm_row_echelon_generic(), DIVIDE_OPERATOR_NAME, entity_intrinsic(), make_com_loopbody(), pips_assert, statement_consistent_p(), and systeme_to_loop_nest().

Referenced by region_to_com_nest().

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

◆ region_to_com_nest()

statement region_to_com_nest ( region  r,
bool  isRead,
int  k 
)

Returns the entity corresponding to the global name.

static entity global_name_to_entity( const char* package, const char* name ) { return gen_find_tabulated(concatenate(package, MODULE_SEP_STRING, name, NULL), entity_domain); }

Definition at line 84 of file communication_generation.c.

84  {
87  type t = entity_type(v);
89  if (type_variable_p(t)) {
90  Psysteme p = region_system(r);
92  // Build the base
96  }
98  }
99  else {
100  pips_internal_error("unexpected type \n");
101  }
102  pips_assert("s is properly generated", statement_consistent_p(s));
103  return s;
104 }
static reference ref
Current stmt (an integer)
Definition: adg_read_paf.c:163
Pbase base_add_variable(Pbase b, Variable var)
Pbase base_add_variable(Pbase b, Variable v): add variable v as a new dimension to basis b at the end...
Definition: base.c:88
bdt base
Current expression.
Definition: bdt_read_paf.c:100
static statement Psysteme_to_loop_nest(entity v, list vl, Pbase b, Psysteme p, bool neighbor, list l_var, int k)
#define region_system(reg)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
list base_to_list(Pbase base)
Most includes are centralized here.
#define pips_internal_error
Definition: misc-local.h:149
#define syntax_reference(x)
Definition: ri.h:2730
#define reference_variable(x)
Definition: ri.h:2326
#define reference_indices(x)
Definition: ri.h:2328
#define entity_type(x)
Definition: ri.h:2792
#define expression_syntax(x)
Definition: ri.h:1247
#define type_variable_p(x)
Definition: ri.h:2947
#define statement_undefined
Definition: ri.h:2419
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
void * Variable
arithmetique is a requirement for vecteur, but I do not want to inforce it in all pips files....
Definition: vecteur-local.h:60
#define BASE_NULLE
MACROS SUR LES BASES.

References base, base_add_variable(), BASE_NULLE, base_to_list(), effect_any_reference, entity_type, expression_syntax, FOREACH, pips_assert, pips_internal_error, Psysteme_to_loop_nest(), ref, reference_indices, reference_variable, region_system, statement_consistent_p(), statement_undefined, syntax_reference, and type_variable_p.

Referenced by com_call().

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

◆ replace_indices_region_com()

static void replace_indices_region_com ( region  r,
list dadd,
int  indNum,
entity  module 
)
static

This function is in charge of replacing the PHI entity of the region by generated indices.

PHI values has no correspondance in the code. Therefore we have to create actual indices and replace them in the region in order for the rest to be build using the right entities.

Definition at line 111 of file communication_generation.c.

111  {
112  Psysteme ps = region_system(r);
114  list ref_indices = reference_indices(ref);
115  list l_var = base_to_list(sc_base(ps));
116  list l_var_new = NIL;
117  list li = NIL;
118  // Default name given to indices
119  char* s = "_rtl";
120  char s2[128];
121  int indIntern = 0;
122  list l_var_temp = gen_nreverse(gen_copy_seq(l_var));
123  bool modified = false;
124  // The objective here is to explore the indices and the variable list we got from the base in order to compare and
125  // treat only the relevant cases
126  FOREACH(entity, e, l_var_temp) {
127  if (!ENDP(ref_indices)) {
128  FOREACH(expression, exp, ref_indices) {
130  if (!strcmp(entity_name(phi), entity_name(e))) {
131  // If the names match, we generate a new name for the variable
132  sprintf(s2, "%s:%s_%d_%d", module_local_name(module),s, indNum, indIntern);
133  indIntern++;
134  // We make a copy of the entity with a new name
135  entity ec = make_entity_copy_with_new_name(e, s2, false);
136  // However the new variable still has a rom type of storage, therefore we create a new ram object
140  s2[0] = '\0';
141  // We build the list we are going to use to rename the variables of our system
142  l_var_new = CONS(ENTITY, ec, l_var_new);
143  // We build the list which will replace the list of indices of the region's reference
144  li = CONS(EXPRESSION, entity_to_expression(ec), li);
145  // We build the list which will be used to build the declaration statement
146  *dadd = CONS(ENTITY, ec, *dadd);
147  modified = true;
148  }
149  }
150  if (!modified) {
151  gen_remove_once(&l_var, e);
152  }
153  }
154  modified = false;
155  }
156  pips_assert("different length \n", gen_length(l_var) == gen_length(l_var_new));
157  // Renaming the variables of the system and replacing the indice list of the region's reference
158  ps = sc_list_variables_rename(ps, l_var, l_var_new);
160  pips_assert("region is not consistent", region_consistent_p(r));
161 }
ram make_ram(entity a1, entity a2, intptr_t a3, list a4)
Definition: ri.c:1999
storage make_storage_ram(ram _field_)
Definition: ri.c:2279
bool region_consistent_p(region reg)
Definition: debug.c:50
Psysteme sc_list_variables_rename(Psysteme, list, list)
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
void gen_remove_once(list *pl, const void *o)
Remove the first occurence of o in list pl:
Definition: list.c:691
list gen_copy_seq(list l)
Copy a list structure.
Definition: list.c:501
#define DYNAMIC_AREA_LOCAL_NAME
Definition: naming-local.h:69
static entity dynamic_area
static char * module
Definition: pips.c:74
int current_offset_of_area(entity a, entity v)
Definition: area.c:174
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 * module_local_name(entity e)
Returns the module local user name.
Definition: entity.c:582
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 entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define entity_storage(x)
Definition: ri.h:2794
#define entity_name(x)
Definition: ri.h:2790

References base_to_list(), CONS, current_offset_of_area(), dynamic_area, DYNAMIC_AREA_LOCAL_NAME, effect_any_reference, ENDP, ENTITY, entity_name, entity_storage, entity_to_expression(), exp, EXPRESSION, expression_syntax, FindEntity(), FOREACH, gen_copy_seq(), gen_full_copy_list(), gen_length(), gen_nreverse(), gen_remove_once(), make_entity_copy_with_new_name(), make_ram(), make_storage_ram(), module, module_local_name(), NIL, pips_assert, ref, reference_indices, reference_variable, region_consistent_p(), region_system, sc_list_variables_rename(), and syntax_reference.

Referenced by com_call().

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

◆ successors()

static list successors ( list  l)
static

Definition at line 229 of file communication_generation.c.

230 {
231  list succs = NIL;
232  FOREACH(SUCCESSOR, su, l) {
233  vertex s = successor_vertex(su);
234  statement child = vertex_to_statement(s);
235  if(gen_occurences(child, succs) == 0)
236  succs = CONS(STATEMENT, child, succs);
237  }
238  return succs;
239 }

References CONS, FOREACH, gen_occurences(), NIL, STATEMENT, SUCCESSOR, successor_vertex, and vertex_to_statement().

Referenced by debug_unstructured(), fs_filter(), gen_send_communications(), if_conversion_compact_stats(), quick_privatize_graph(), quick_privatize_loop(), reduce_sequence(), remove_dependances_from_successors(), replace_control_with_unstructured(), some_conflicts_between(), and statements_to_successors().

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

◆ transfer_regions()

static list transfer_regions ( statement  parent,
statement  child 
)
static

Definition at line 191 of file communication_generation.c.

192 {
196 }
list RegionsIntersection(list l1, list l2, bool(*intersection_combinable_p)(effect, effect))
list RegionsIntersection(list l1,l2, bool (*intersection_combinable_p)(effect, effect)) input : outpu...
bool w_r_combinable_p(effect, effect)

References load_statement_in_regions(), load_statement_out_regions(), regions_dup(), RegionsIntersection(), and w_r_combinable_p().

Referenced by gen_recv_communications(), and gen_send_communications().

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