PIPS
compile_regions.c File Reference
#include "defines-local.h"
#include "prettyprint.h"
+ Include dependency graph for compile_regions.c:

Go to the source code of this file.

Functions

static bool combinable_regions_p (region r1, region r2)
 Copyright 2007-2012 Alain Muller, Frederique Silber-Chaussumier. More...
 
static bool region_interlaced_p (list send_regions, region r)
 
static bool reduction_p (set reductions_l[STEP_UNDEF_REDUCE], entity e)
 
static bool comm_partial_p (list send_regions, region r)
 
static statement bound_to_statement (entity mpi_module, list expr_bound, entity array_region, string bound_name, int dim, list index)
 
static list phi_free_contraints_to_expressions (bool equality, region reg)
 
static bool contraintes_to_expression (bool equality, entity phi, Psysteme sys, list *expr_l, list *expr_u)
 
static void compute_region (entity mpi_module, region reg, entity array_region, bool loop_p, statement *compute_regions_stmt)
 
static bool region_reduction_p (set reductions_l[STEP_UNDEF_REDUCE], region reg)
 
static void generate_call_set_regionarray (entity mpi_module, region reg, entity array_region, bool loop_p, bool is_reduction, bool is_interlaced, statement *set_regions_stmt)
 
static void generate_call_stepalltoall (entity mpi_module, region reg, bool is_reduction, bool is_interlaced, bool is_partial, statement *stepalltoall_stmt)
 pourquoi flush et non pas alltoall ? More...
 
static void region_to_statement (entity mpi_module, region reg, bool loop_p, bool is_reduction, bool is_interlaced, bool is_partial, statement *compute_regions_stmt, statement *set_regionarray_stmt, statement *stepalltoall_stmt)
 
static void transform_regions_to_statement (entity mpi_module, list regions_l, bool loop_p, list send_as_comm_l, set reductions_l[STEP_UNDEF_REDUCE], statement *compute_regions_stmt, statement *set_regionarray_stmt, statement *stepalltoall_stmt)
 
static void add_workchunk_loop (entity mpi_module, bool loop_p, loop loop_stmt, statement *compute_regions_stmt)
 
void compile_regions (entity new_module, list regions_l, bool loop_p, loop loop_stmt, list send_as_comm_l, set reductions_l[STEP_UNDEF_REDUCE], statement mpi_begin_stmt, statement mpi_end_stmt)
 

Function Documentation

◆ add_workchunk_loop()

static void add_workchunk_loop ( entity  mpi_module,
bool  loop_p,
loop  loop_stmt,
statement compute_regions_stmt 
)
static

Definition at line 481 of file compile_regions.c.

482 {
483  pips_debug(1, "begin\n");
484  /*
485  ajout de la boucle parcourant les workchunks
486  suppression du test !entity_undefined_p(index) : redondant avec loop_p?
487  */
488  if( loop_p &&
489  !ENDP(statement_block(*compute_regions_stmt)))
490  {
491  generate_call_get_workchunk_loopbounds(mpi_module, loop_stmt, compute_regions_stmt);
492 
493  generate_loop_workchunk(mpi_module, compute_regions_stmt);
494  }
495  pips_debug(1, "end\n");
496 }
void generate_call_get_workchunk_loopbounds(entity mpi_module, loop loop_stmt, statement *compute_regions_stmt)
Definition: compile_RT.c:119
void generate_loop_workchunk(entity mpi_module, statement *compute_regions_stmt)
Definition: compile_RT.c:101
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
list statement_block(statement)
Get the list of block statements of a statement sequence.
Definition: statement.c:1338
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145

References ENDP, generate_call_get_workchunk_loopbounds(), generate_loop_workchunk(), pips_debug, and statement_block().

Referenced by compile_regions().

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

◆ bound_to_statement()

static statement bound_to_statement ( entity  mpi_module,
list  expr_bound,
entity  array_region,
string  bound_name,
int  dim,
list  index 
)
static

Definition at line 96 of file compile_regions.c.

97 {
98  pips_debug(1, "begin array_region = %p\n", array_region);
99 
100  pips_assert("expression", !ENDP(expr_bound));
101  statement s;
103  list dims = CONS(EXPRESSION, step_symbolic_expression(bound_name, mpi_module),
105 
106  bool is_fortran = fortran_module_p(get_current_module_entity());
107  if (!is_fortran)
108  {
109  list l = NIL;
110  FOREACH(EXPRESSION, e, dims)
111  {
113  e,
114  int_to_expression(1)),
115  l);
116  }
117  dims = l;
118  }
119 
120  expression expr = reference_to_expression(make_reference(array_region, dims));
121 
122  if ( gen_length(expr_bound) != 1 )
123  {
124  if(strncmp(bound_name, STEP_INDEX_SLICE_LOW_NAME, strlen(bound_name)) == 0)
126  else if (strncmp(bound_name, STEP_INDEX_SLICE_UP_NAME, strlen(bound_name)) == 0)
128  else
129  pips_internal_error("unexpected bound name %s", bound_name);
130  s = make_assign_statement(expr, call_to_expression(make_call(op, expr_bound)));
131  }
132  else
133  s = make_assign_statement(expr, EXPRESSION(CAR(expr_bound)));
134 
135  pips_debug(1, "end\n");
136  return s;
137 }
call make_call(entity a1, list a2)
Definition: ri.c:269
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
#define STEP_INDEX_SLICE_LOW_NAME
Definition: STEP_name.h:26
#define STEP_INDEX_SLICE_UP_NAME
Definition: STEP_name.h:27
expression step_symbolic_expression(string name, entity module)
Definition: compile_RT.c:353
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
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
list gen_full_copy_list(list l)
Copy a list structure with element copy.
Definition: list.c:535
statement make_assign_statement(expression, expression)
Definition: statement.c:583
#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 MAX_OPERATOR_NAME
#define MINUS_C_OPERATOR_NAME
#define MIN_OPERATOR_NAME
bool fortran_module_p(entity m)
Test if a module is in Fortran.
Definition: entity.c:2799
entity CreateIntrinsic(string name)
this function does not create an intrinsic function because they must all be created beforehand by th...
Definition: entity.c:1311
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
expression reference_to_expression(reference r)
Definition: expression.c:196
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
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 call_to_expression(call c)
Build an expression that call a function or procedure.
Definition: expression.c:309
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_undefined
Definition: ri.h:2761
The structure used to build lists in NewGen.
Definition: newgen_list.h:41

References call_to_expression(), CAR, CONS, CreateIntrinsic(), ENDP, entity_intrinsic(), entity_undefined, EXPRESSION, FOREACH, fortran_module_p(), gen_full_copy_list(), gen_length(), get_current_module_entity(), int_to_expression(), make_assign_statement(), make_call(), make_reference(), MakeBinaryCall(), MAX_OPERATOR_NAME, MIN_OPERATOR_NAME, MINUS_C_OPERATOR_NAME, NIL, pips_assert, pips_debug, pips_internal_error, reference_to_expression(), STEP_INDEX_SLICE_LOW_NAME, STEP_INDEX_SLICE_UP_NAME, and step_symbolic_expression().

Referenced by compute_region().

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

◆ combinable_regions_p()

static bool combinable_regions_p ( region  r1,
region  r2 
)
static

Copyright 2007-2012 Alain Muller, Frederique Silber-Chaussumier.

This file is part of STEP.

The program is distributed under the terms of the GNU General Public License.

Definition at line 19 of file compile_regions.c.

20 {
21  bool same_var, same_act;
22 
24  return(true);
25 
26  same_var = (region_entity(r1) == region_entity(r2));
27  same_act = action_equal_p(region_action(r1), region_action(r2));
28 
29  return(same_var && same_act);
30 }
#define region_action(reg)
#define region_entity(reg)
#define region_undefined_p(reg)
bool action_equal_p(action, action)
Definition: effects.c:1023

References action_equal_p(), region_action, region_entity, and region_undefined_p.

Referenced by comm_partial_p(), and region_interlaced_p().

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

◆ comm_partial_p()

static bool comm_partial_p ( list  send_regions,
region  r 
)
static

Definition at line 70 of file compile_regions.c.

71 {
72  bool partial_p = true;
73  pips_debug(1, "begin\n");
74  if(region_write_p(r))
75  {
76  bool first = true;
77 
78  FOREACH(REGION, reg, send_regions)
79  {
80  if(combinable_regions_p(reg, r))
81  {
82  assert(first);
83  partial_p = step_partial_p(reg);
84  first = false;
85  }
86  }
87  }
88  pips_debug(1, "end partial_p = %d\n", partial_p);
89  return partial_p;
90 }
bool step_partial_p(region reg)
Definition: analyse.c:173
static bool combinable_regions_p(region r1, region r2)
Copyright 2007-2012 Alain Muller, Frederique Silber-Chaussumier.
#define region_write_p(reg)
#define REGION
#define assert(ex)
Definition: newgen_assert.h:41

References assert, combinable_regions_p(), FOREACH, pips_debug, REGION, region_write_p, and step_partial_p().

Referenced by transform_regions_to_statement().

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

◆ compile_regions()

void compile_regions ( entity  new_module,
list  regions_l,
bool  loop_p,
loop  loop_stmt,
list  send_as_comm_l,
set  reductions_l[STEP_UNDEF_REDUCE],
statement  mpi_begin_stmt,
statement  mpi_end_stmt 
)

Definition at line 498 of file compile_regions.c.

499 {
500  statement compute_regions_stmt, set_regions_stmt, flush_regions_stmt;
501 
502  pips_debug(1, "begin regions_l = %p\n", regions_l);
503 
504  transform_regions_to_statement(new_module, regions_l, loop_p, send_as_comm_l, reductions_l,
505  &compute_regions_stmt, &set_regions_stmt, &flush_regions_stmt);
506 
507  add_workchunk_loop(new_module, loop_p, loop_stmt, &compute_regions_stmt);
508  generate_call_flush(&flush_regions_stmt);
509 
510  if(!ENDP(statement_block(compute_regions_stmt)))
511  {
512  string comment;
513  statement comment_stmt = make_plain_continue_statement();
514  insert_statement(mpi_begin_stmt, comment_stmt, false);
515  insert_statement(mpi_begin_stmt, compute_regions_stmt, false);
516  insert_statement(mpi_begin_stmt, set_regions_stmt, false);
517 
518  if (list_undefined_p(send_as_comm_l))
519  {
520  comment = strdup("\nRECV REGIONS");
521  insert_statement(mpi_begin_stmt, flush_regions_stmt, false);
522  }
523  else
524  {
525  comment = strdup("\nSEND REGIONS");
526  insert_statement(mpi_end_stmt, flush_regions_stmt, false);
527  }
528  put_a_comment_on_a_statement(comment_stmt, comment);
529  }
530  else
531  {
532  free_statement(compute_regions_stmt);
533  free_statement(set_regions_stmt);
534  free_statement(flush_regions_stmt);
535  }
536 
537 }
void free_statement(statement p)
Definition: ri.c:2189
void generate_call_flush(statement *stepalltoall_stmt)
Definition: compile_RT.c:85
static void transform_regions_to_statement(entity mpi_module, list regions_l, bool loop_p, list send_as_comm_l, set reductions_l[STEP_UNDEF_REDUCE], statement *compute_regions_stmt, statement *set_regionarray_stmt, statement *stepalltoall_stmt)
static void add_workchunk_loop(entity mpi_module, bool loop_p, loop loop_stmt, statement *compute_regions_stmt)
static void comment(string_buffer code, spoc_hardware_type hw, dagvtx v, int stage, int side, bool flip)
Definition: freia_spoc.c:52
#define list_undefined_p(c)
Return if a list is undefined.
Definition: newgen_list.h:75
void put_a_comment_on_a_statement(statement, string)
Similar to try_to_put_a_comment_on_a_statement() but insert a CONTINUE to put the comment on it if th...
Definition: statement.c:1863
void insert_statement(statement, statement, bool)
This is the normal entry point.
Definition: statement.c:2570
statement make_plain_continue_statement(void)
Make a simple continue statement to be used as a NOP or ";" in C.
Definition: statement.c:964
char * strdup()

References add_workchunk_loop(), comment(), ENDP, free_statement(), generate_call_flush(), insert_statement(), list_undefined_p, make_plain_continue_statement(), pips_debug, put_a_comment_on_a_statement(), statement_block(), strdup(), and transform_regions_to_statement().

Referenced by compile_body().

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

◆ compute_region()

static void compute_region ( entity  mpi_module,
region  reg,
entity  array_region,
bool  loop_p,
statement compute_regions_stmt 
)
static

Definition at line 263 of file compile_regions.c.

264 {
265  pips_debug(1, "begin array_region = %p\n", array_region);
266  Psysteme sys = region_system(reg);
268 
269  if(ENDP(bounds_array))
270  {
271  pips_debug(0,"Current array : %s\n", entity_name(region_entity(reg)));
272  pips_assert("defined array bounds", 0);
273  }
274 
275  list index_slice = NIL;
276  if (loop_p)
277  {
278  entity workchunk_id = step_local_slice_index(mpi_module);
279  index_slice = CONS(EXPRESSION, entity_to_expression(workchunk_id), index_slice);
280  }
281 
282  statement empty_region_stmt = statement_undefined;
283  list phi_free_contraints = NIL;
284  phi_free_contraints = gen_nconc(phi_free_contraints_to_expressions(true, reg), phi_free_contraints);
285  phi_free_contraints = gen_nconc(phi_free_contraints_to_expressions(false, reg), phi_free_contraints);
286  if (!ENDP(phi_free_contraints))
287  empty_region_stmt = make_empty_block_statement();
288 
289  statement compute_region_stmt = make_empty_block_statement();
290  int dim = 0;
291 
292  // on parcourt dans l'ordre des indices (PHI1, PHI2, ...) chaque PHIi correspond a une dimension dim
293 
295  {
296  list expr_l = NIL;
297  list expr_u = NIL;
299  dimension bounds_d = DIMENSION(gen_nth(dim, bounds_array)); // gen_nth numerote les element a partir de 0 et ...
300  dim++; // ... les tableaux de region numerote les dimensions a partir de 1
301 
302  // on determine les listes d'expression expr_l (et expr_u) correspondant aux
303  // contraites low (et up) portant sur la variable PHI courante
304  // ex: L <= PHI1 + 1 et PHI1 -1 <= U
305  // expr_l contient l'expression (L-1) et expr_u contient l'expression (U+1)
306 
307  // pips_assert("empty list", ENDP(expr_l) && ENDP(expr_u));
308  // recherche et transformation des contraintes d'equalites portant sur phi
309  contraintes_to_expression(true, phi, sys, &expr_l, &expr_u);
310  // recherche et transformation des contraintes d'inequalites portant sur phi
311  contraintes_to_expression(false, phi, sys, &expr_l, &expr_u);
312 
313  // ajout contraintes liees aux bornes d'indexation du tableau pour la dimension courante
314  if(ENDP(expr_l))
315  expr_l = CONS(EXPRESSION, copy_expression(dimension_lower(bounds_d)), expr_l);
316  if(ENDP(expr_u))
317  expr_u = CONS(EXPRESSION, copy_expression(dimension_upper(bounds_d)), expr_u);
318 
319  /*
320  generation des statements : array_region(bound_name, dim, index_slice) = expr_bound
321  */
322  statement b1 = bound_to_statement(mpi_module, expr_l, array_region, STEP_INDEX_SLICE_LOW_NAME, dim, index_slice);
323  statement b2 = bound_to_statement(mpi_module, expr_u, array_region, STEP_INDEX_SLICE_UP_NAME, dim, index_slice);
324 
325  ifdebug(2)
326  {
327  pips_debug(2, "b1\n");
329  pips_debug(2, "b2\n");
331  }
332  insert_statement(compute_region_stmt, b1, false);
333  insert_statement(compute_region_stmt, b2, false);
334 
335  if (!ENDP(phi_free_contraints))
336  {
337  expr_l = CONS(EXPRESSION, copy_expression(dimension_upper(bounds_d)), NIL);
338  expr_u = CONS(EXPRESSION, copy_expression(dimension_lower(bounds_d)), NIL);
339 
340  b1 = bound_to_statement(mpi_module, expr_l, array_region, STEP_INDEX_SLICE_LOW_NAME, dim, index_slice);
341  b2 = bound_to_statement(mpi_module, expr_u, array_region, STEP_INDEX_SLICE_UP_NAME, dim, index_slice);
342 
343  insert_statement(empty_region_stmt, b1, false);
344  insert_statement(empty_region_stmt, b2, false);
345  }
346 
347  }
348 
349  if (!ENDP(phi_free_contraints))
350  {
352  expression cond_expr = expression_list_to_binary_operator_call(phi_free_contraints, and_op);
353 
354  insert_statement(*compute_regions_stmt,
356  make_test(cond_expr,
357  compute_region_stmt,
358  empty_region_stmt))),
359  false);
360  string comment_str = strdup(" Inverted bounds correspond to empty regions\n Used when work concerns specific data ex: print A[5]\n In this case, only concerned process sends non empty regions\n");
361  put_a_comment_on_a_statement(empty_region_stmt, comment_str);
362  }
363  else
364  insert_statement(*compute_regions_stmt, compute_region_stmt, false);
365 
366  pips_debug(1, "end\n");
367 }
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
test make_test(expression a1, statement a2, statement a3)
Definition: ri.c:2607
instruction make_instruction(enum instruction_utype tag, void *val)
Definition: ri.c:1166
entity step_local_slice_index(entity module)
Definition: compile_RT.c:486
static statement bound_to_statement(entity mpi_module, list expr_bound, entity array_region, string bound_name, int dim, list index)
static bool contraintes_to_expression(bool equality, entity phi, Psysteme sys, list *expr_l, list *expr_u)
static list phi_free_contraints_to_expressions(bool equality, region reg)
#define region_system(reg)
#define effect_any_reference(e)
FI: cannot be used as a left hand side.
statement instruction_to_statement(instruction)
Build a statement from a give instruction.
Definition: statement.c:597
statement make_empty_block_statement(void)
Build an empty statement (block/sequence)
Definition: statement.c:625
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
gen_chunk gen_nth(int n, const list l)
to be used as ENTITY(gen_nth(3, l))...
Definition: list.c:710
void print_statement(statement)
Print a statement on stderr.
Definition: statement.c:98
#define C_AND_OPERATOR_NAME
#define AND_OPERATOR_NAME
FI: intrinsics are defined at a third place after bootstrap and effects! I guess the name should be d...
bool c_module_p(entity m)
Test if a module "m" is written in C.
Definition: entity.c:2777
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression expression_list_to_binary_operator_call(list l, entity op)
Definition: expression.c:1917
#define syntax_reference(x)
Definition: ri.h:2730
#define reference_variable(x)
Definition: ri.h:2326
#define dimension_lower(x)
Definition: ri.h:980
#define type_variable(x)
Definition: ri.h:2949
@ is_instruction_test
Definition: ri.h:1470
#define entity_name(x)
Definition: ri.h:2790
#define dimension_upper(x)
Definition: ri.h:982
#define reference_indices(x)
Definition: ri.h:2328
#define variable_dimensions(x)
Definition: ri.h:3122
#define entity_type(x)
Definition: ri.h:2792
#define expression_syntax(x)
Definition: ri.h:1247
#define statement_undefined
Definition: ri.h:2419
Value b2
Definition: sc_gram.c:105
Value b1
booleen indiquant quel membre est en cours d'analyse
Definition: sc_gram.c:105
#define ifdebug(n)
Definition: sg.c:47

References AND_OPERATOR_NAME, b1, b2, bound_to_statement(), C_AND_OPERATOR_NAME, c_module_p(), CONS, contraintes_to_expression(), copy_expression(), DIMENSION, dimension_lower, dimension_upper, effect_any_reference, ENDP, entity_intrinsic(), entity_name, entity_to_expression(), entity_type, EXPRESSION, expression_list_to_binary_operator_call(), expression_syntax, FOREACH, gen_nconc(), gen_nth(), get_current_module_entity(), ifdebug, insert_statement(), instruction_to_statement(), is_instruction_test, make_empty_block_statement(), make_instruction(), make_test(), NIL, phi_free_contraints_to_expressions(), pips_assert, pips_debug, print_statement(), put_a_comment_on_a_statement(), reference_indices, reference_variable, region_entity, region_system, statement_undefined, STEP_INDEX_SLICE_LOW_NAME, STEP_INDEX_SLICE_UP_NAME, step_local_slice_index(), strdup(), syntax_reference, type_variable, and variable_dimensions.

Referenced by region_to_statement().

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

◆ contraintes_to_expression()

static bool contraintes_to_expression ( bool  equality,
entity  phi,
Psysteme  sys,
list expr_l,
list expr_u 
)
static

Definition at line 194 of file compile_regions.c.

195 {
196  Pcontrainte c;
197  bool found_equality=false;
198 
199  pips_debug(1, "begin\n");
200  for(c = equality?sc_egalites(sys):sc_inegalites(sys); !found_equality && !CONTRAINTE_UNDEFINED_P(c); c = c->succ)
201  {
202  int coef_phi=VALUE_TO_INT(vect_coeff((Variable)phi,c->vecteur));
203  if(coef_phi != 0)
204  {
205  expression expr;
206  Pvecteur coord,v = vect_del_var(c->vecteur, (Variable)phi);
207  bool up_bound = (coef_phi > 0);
208  bool low_bound = !up_bound;
209 
210  //construction des expressions d'affectation
211  if(VECTEUR_NUL_P(v))
212  expr = int_to_expression(0);
213  else
214  {
215  if (coef_phi > 0) //contrainte de type : coef_phi*phi <= "vecteur"
216  {
217  for (coord = v; coord!=NULL; coord=coord->succ)
218  val_of(coord) = -val_of(coord);
219  coef_phi = -coef_phi;
220  }
221 
222  expr = make_vecteur_expression(v);
223  if (coef_phi != -1)
224  expr = make_op_exp("/", expr, int_to_expression(-coef_phi));
225  }
226 
227  if (equality || low_bound)
228  *expr_l = CONS(EXPRESSION,copy_expression(expr), *expr_l);
229  if (equality || up_bound)
230  *expr_u = CONS(EXPRESSION,copy_expression(expr), *expr_u);
231 
232  free_expression(expr);
233  found_equality = equality;
234  }
235  }
236  pips_debug(1, "end\n");
237  return found_equality;
238 }
void free_expression(expression p)
Definition: ri.c:853
#define VALUE_TO_INT(val)
#define CONTRAINTE_UNDEFINED_P(c)
expression make_vecteur_expression(Pvecteur pv)
make expression for vector (Pvecteur)
Definition: expression.c:1650
expression make_op_exp(char *op_name, expression exp1, expression exp2)
================================================================
Definition: expression.c:2012
Pvecteur vecteur
struct Scontrainte * succ
le type des coefficients dans les vecteurs: Value est defini dans le package arithmetique
Definition: vecteur-local.h:89
struct Svecteur * succ
Definition: vecteur-local.h:92
#define val_of(varval)
#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
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

References CONS, CONTRAINTE_UNDEFINED_P, copy_expression(), EXPRESSION, free_expression(), int_to_expression(), make_op_exp(), make_vecteur_expression(), pips_debug, Scontrainte::succ, Svecteur::succ, val_of, VALUE_TO_INT, vect_coeff(), vect_del_var(), Scontrainte::vecteur, and VECTEUR_NUL_P.

Referenced by compute_region().

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

◆ generate_call_set_regionarray()

static void generate_call_set_regionarray ( entity  mpi_module,
region  reg,
entity  array_region,
bool  loop_p,
bool  is_reduction,
bool  is_interlaced,
statement set_regions_stmt 
)
static

Definition at line 376 of file compile_regions.c.

377 {
378  pips_debug(1, "begin\n");
379 
380  entity array = region_entity(reg);
381 
382  expression expr_nb_workchunk = loop_p?entity_to_expression(get_entity_step_commsize(mpi_module)):int_to_expression(1);
383  statement set_stmt = region_read_p(reg)?
384  build_call_STEP_set_recvregions(array, expr_nb_workchunk, array_region):
385  build_call_STEP_set_sendregions(array, expr_nb_workchunk, array_region, is_interlaced, is_reduction);
386  insert_statement(*set_regions_stmt, set_stmt, false);
387 
388  pips_debug(1, "end\n");
389 }
statement build_call_STEP_set_recvregions(entity user_array, expression expr_nb_workchunk, entity regions_array)
Definition: compile_RT.c:736
entity get_entity_step_commsize(entity module)
Que signifie local?
Definition: compile_RT.c:519
statement build_call_STEP_set_sendregions(entity user_array, expression expr_nb_workchunk, entity regions_array, bool is_interlaced, bool is_reduction)
Definition: compile_RT.c:701
#define region_read_p(reg)
useful region macros
static entity array

References array, build_call_STEP_set_recvregions(), build_call_STEP_set_sendregions(), entity_to_expression(), get_entity_step_commsize(), insert_statement(), int_to_expression(), pips_debug, region_entity, and region_read_p.

Referenced by region_to_statement().

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

◆ generate_call_stepalltoall()

static void generate_call_stepalltoall ( entity  mpi_module,
region  reg,
bool  is_reduction,
bool  is_interlaced,
bool  is_partial,
statement stepalltoall_stmt 
)
static

pourquoi flush et non pas alltoall ?

Definition at line 392 of file compile_regions.c.

393 {
394  entity array = region_entity(reg);
395 
396  if(!is_reduction)
397  {
398  statement comm_stmt = build_call_STEP_AllToAll(mpi_module, array, is_partial, is_interlaced);
399  insert_statement(*stepalltoall_stmt, comm_stmt, false);
400  }
401 }
statement build_call_STEP_AllToAll(entity module, entity array, bool is_partial, bool is_interlaced)
Definition: compile_RT.c:640

References array, build_call_STEP_AllToAll(), insert_statement(), and region_entity.

Referenced by region_to_statement().

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

◆ phi_free_contraints_to_expressions()

static list phi_free_contraints_to_expressions ( bool  equality,
region  reg 
)
static

Definition at line 139 of file compile_regions.c.

140 {
141  Psysteme sys = region_system(reg);
142  Pcontrainte c;
143  list expression_l = NIL;
144 
145  entity comparator;
148  else
150 
151  for(c = equality?sc_egalites(sys):sc_inegalites(sys); !CONTRAINTE_UNDEFINED_P(c); c = c->succ)
152  {
153  int coef_phi = 0;
155  {
157  coef_phi = VALUE_TO_INT(vect_coeff((Variable)phi,c->vecteur));
158  if(coef_phi != 0)
159  break;
160  }
161  if(coef_phi == 0)
162  {
163  expression expr = MakeBinaryCall(comparator,
165  int_to_expression(0));
166  expression_l = CONS(EXPRESSION, expr, expression_l);
167  }
168  }
169  return expression_l;
170 }
#define C_LESS_OR_EQUAL_OPERATOR_NAME
#define EQUAL_OPERATOR_NAME
#define LESS_OR_EQUAL_OPERATOR_NAME
#define C_EQUAL_OPERATOR_NAME

References C_EQUAL_OPERATOR_NAME, C_LESS_OR_EQUAL_OPERATOR_NAME, c_module_p(), CONS, CONTRAINTE_UNDEFINED_P, effect_any_reference, entity_intrinsic(), EQUAL_OPERATOR_NAME, EXPRESSION, expression_syntax, FOREACH, get_current_module_entity(), int_to_expression(), LESS_OR_EQUAL_OPERATOR_NAME, make_vecteur_expression(), MakeBinaryCall(), NIL, reference_indices, reference_variable, region_system, Scontrainte::succ, syntax_reference, VALUE_TO_INT, vect_coeff(), and Scontrainte::vecteur.

Referenced by compute_region().

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

◆ reduction_p()

static bool reduction_p ( set  reductions_l[STEP_UNDEF_REDUCE],
entity  e 
)
static

Definition at line 55 of file compile_regions.c.

56 {
57  bool is_reduction = false;
58  int op;
59 
60  pips_debug(1, "begin\n");
61 
62  for(op=0; !is_reduction && op<STEP_UNDEF_REDUCE; op++)
63  is_reduction = set_belong_p(reductions_l[op], e);
64 
65  pips_debug(1, "end\n");
66  return is_reduction;
67 }
bool set_belong_p(const set, const void *)
Definition: set.c:194
#define STEP_UNDEF_REDUCE
Definition: step_common.h:95

References pips_debug, set_belong_p(), and STEP_UNDEF_REDUCE.

Referenced by compile_body(), pointer_to_initial_name(), region_reduction_p(), and step_get_directive_reductions().

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

◆ region_interlaced_p()

static bool region_interlaced_p ( list  send_regions,
region  r 
)
static

Definition at line 32 of file compile_regions.c.

33 {
34  bool interlaced = false;
35  pips_debug(1, "begin send_regions = %p, r = %p\n", send_regions, r);
36 
37  if(region_write_p(r))
38  {
39  bool first = true;
40 
41  FOREACH(REGION, reg, send_regions)
42  {
43  if(combinable_regions_p(reg, r))
44  {
45  assert(first);
46  interlaced = step_interlaced_p(reg);
47  first = false;
48  }
49  }
50  }
51  pips_debug(1, "end\n");
52  return interlaced;
53 }
bool step_interlaced_p(region reg)
Definition: analyse.c:167

References assert, combinable_regions_p(), FOREACH, pips_debug, REGION, region_write_p, and step_interlaced_p().

Referenced by transform_regions_to_statement().

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

◆ region_reduction_p()

static bool region_reduction_p ( set  reductions_l[STEP_UNDEF_REDUCE],
region  reg 
)
static

Definition at line 369 of file compile_regions.c.

370 {
371  entity array = region_entity(reg);
372 
373  return region_write_p(reg) && reduction_p(reductions_l, array);
374 }
static bool reduction_p(set reductions_l[STEP_UNDEF_REDUCE], entity e)

References array, reduction_p(), region_entity, and region_write_p.

Referenced by transform_regions_to_statement().

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

◆ region_to_statement()

static void region_to_statement ( entity  mpi_module,
region  reg,
bool  loop_p,
bool  is_reduction,
bool  is_interlaced,
bool  is_partial,
statement compute_regions_stmt,
statement set_regionarray_stmt,
statement stepalltoall_stmt 
)
static

bug bug bug si on inverse les instr expr_nb_region et region_array_name alors bug. POURQUOI??

Definition at line 403 of file compile_regions.c.

404 {
405  pips_debug(1,"begin mpi_module = %s, region = %p\n", entity_name(mpi_module), reg);
406 
407  entity array = region_entity(reg);
408  pips_debug(2, "array = %s\n", entity_name(array));
409 
410  /*
411  Elimination of redundancies
412  */
414 
415  /*
416  Add region description in comments
417  */
418  string str_eff = text_to_string(text_rw_array_regions(CONS(REGION, reg, NIL)));
419  statement comment_stmt = make_plain_continue_statement();
420  put_a_comment_on_a_statement(comment_stmt, str_eff);
421 
422  insert_statement(*compute_regions_stmt, comment_stmt, false);
423 
424 
425  /*
426  Create STEP_RR and STEP_SR array entities
427  */
429 
430  /* bug bug bug si on inverse les instr expr_nb_region et region_array_name alors bug. POURQUOI??*/
431 
432  string region_array_name = region_read_p(reg)?STEP_RR_NAME(array):STEP_SR_NAME(array);
433  pips_debug(2, "region_array_name = %s\n", region_array_name);
434 
435  entity region_array = step_local_regionArray(mpi_module, array, region_array_name, expr_nb_region);
436  pips_debug(2, "region_array = %p\n", region_array);
437 
438  /*
439  Compute regions
440  */
441  compute_region(mpi_module, reg, region_array, loop_p, compute_regions_stmt);
442 
443  /*
444  Set regions
445  */
446 
447  generate_call_set_regionarray(mpi_module, reg, region_array, loop_p, is_reduction, is_interlaced, set_regionarray_stmt);
448 
449  /*
450  stepalltoall_stmt
451 
452  Pour les régions SEND ET (?) RECV
453  */
454 
455  generate_call_stepalltoall(mpi_module, reg, is_reduction, is_interlaced, is_partial, stepalltoall_stmt);
456 
457  pips_debug(1, "end\n");
458 }
#define STEP_MAX_NB_LOOPSLICES_NAME
Definition: STEP_name.h:34
#define STEP_SR_NAME(array)
Definition: STEP_name.h:11
#define STEP_RR_NAME(array)
Definition: STEP_name.h:12
entity step_local_regionArray(entity module, entity array, string region_array_name, expression expr_nb_region)
Definition: compile_RT.c:428
static void generate_call_stepalltoall(entity mpi_module, region reg, bool is_reduction, bool is_interlaced, bool is_partial, statement *stepalltoall_stmt)
pourquoi flush et non pas alltoall ?
static void generate_call_set_regionarray(entity mpi_module, region reg, entity array_region, bool loop_p, bool is_reduction, bool is_interlaced, statement *set_regions_stmt)
static void compute_region(entity mpi_module, region reg, entity array_region, bool loop_p, statement *compute_regions_stmt)
text text_rw_array_regions(list)
#define expression_undefined
Definition: ri.h:1223
Psysteme sc_safe_elim_redund(Psysteme ps)
Same as above, but the basis is preserved and sc_empty is returned is the system is not feasible.
string text_to_string(text t)
SG: moved here from ricedg.
Definition: print.c:239

References array, compute_region(), CONS, entity_name, expression_undefined, generate_call_set_regionarray(), generate_call_stepalltoall(), insert_statement(), make_plain_continue_statement(), NIL, pips_debug, put_a_comment_on_a_statement(), REGION, region_entity, region_read_p, region_system, sc_safe_elim_redund(), step_local_regionArray(), STEP_MAX_NB_LOOPSLICES_NAME, STEP_RR_NAME, STEP_SR_NAME, step_symbolic_expression(), text_rw_array_regions(), and text_to_string().

Referenced by transform_regions_to_statement().

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

◆ transform_regions_to_statement()

static void transform_regions_to_statement ( entity  mpi_module,
list  regions_l,
bool  loop_p,
list  send_as_comm_l,
set  reductions_l[STEP_UNDEF_REDUCE],
statement compute_regions_stmt,
statement set_regionarray_stmt,
statement stepalltoall_stmt 
)
static

Definition at line 460 of file compile_regions.c.

462 {
463  pips_debug(1, "begin regions_l = %p, pure_send_l = %p\n", regions_l, send_as_comm_l);
464 
465  *compute_regions_stmt = make_empty_block_statement();
466  *set_regionarray_stmt = make_empty_block_statement();
467  *stepalltoall_stmt = make_empty_block_statement();
468 
469  FOREACH(REGION, reg, regions_l)
470  {
471  bool is_reduction = region_reduction_p(reductions_l, reg);
472  bool is_interlaced = region_interlaced_p(send_as_comm_l, reg);
473  bool is_partial = comm_partial_p(send_as_comm_l, reg);
474 
475  region_to_statement(mpi_module, reg, loop_p, is_reduction, is_interlaced, is_partial, compute_regions_stmt, set_regionarray_stmt, stepalltoall_stmt);
476  }
477 
478  pips_debug(1, "end\n");
479 }
static void region_to_statement(entity mpi_module, region reg, bool loop_p, bool is_reduction, bool is_interlaced, bool is_partial, statement *compute_regions_stmt, statement *set_regionarray_stmt, statement *stepalltoall_stmt)
static bool comm_partial_p(list send_regions, region r)
static bool region_interlaced_p(list send_regions, region r)
static bool region_reduction_p(set reductions_l[STEP_UNDEF_REDUCE], region reg)

References comm_partial_p(), FOREACH, make_empty_block_statement(), pips_debug, REGION, region_interlaced_p(), region_reduction_p(), and region_to_statement().

Referenced by compile_regions().

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