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

Go to the source code of this file.

Macros

#define debug_print_control(c, w)
 

Functions

static void hpf_compile_block (statement stat, statement *hoststatp, statement *nodestatp)
 
static void hpf_compile_test (statement s, statement *hoststatp, statement *nodestatp)
 
static list caller_list_of_bounds (_UNUSED_ entity fun, list le)
 return the list of bounds More...
 
static void hpf_compile_call (statement stat, statement *hoststatp, statement *nodestatp)
 returned node version More...
 
static void compile_control (control c, statement_mapping maph, statement_mapping mapn)
 
static void hpf_compile_unstructured (statement stat, statement *hoststatp, statement *nodestatp)
 
static void hpf_compile_sequential_loop (statement stat, statement *hoststatp, statement *nodestatp)
 
static void hpf_compile_parallel_body (statement body, statement *hoststatp, statement *nodestatp)
 
static void hpf_compile_parallel_loop (statement stat, statement *hoststatp, statement *nodestatp)
 
static bool loop_flt (loop l)
 
static bool parallel_loop_in_stat_p (statement s)
 
static void hpf_compile_loop (statement stat, statement *hoststatp, statement *nodestatp)
 
void hpf_compiler (statement stat, statement *hoststatp, statement *nodestatp)
 what: compile a statement into a host and SPMD node code. More...
 

Variables

entity host_module
 HPFC - Fabien Coelho, May 1993 and later... More...
 
entity node_module
 
static bool parallel_loop_found
 is there a parallel loop down s? More...
 

Macro Definition Documentation

◆ debug_print_control

#define debug_print_control (   c,
 
)
Value:
fprintf(stderr, \
"%s: ctr %p (stat %p) , %zd preds, %zd succs\n", w, \
print_statement(control_statement(c));
size_t gen_length(const list l)
Definition: list.c:150
#define control_predecessors(x)
Definition: ri.h:943
#define control_successors(x)
Definition: ri.h:945
#define control_statement(x)
Definition: ri.h:941
int fprintf()
test sc_min : ce test s'appelle par : programme fichier1.data fichier2.data ...

Definition at line 49 of file compiler.c.

Function Documentation

◆ caller_list_of_bounds()

static list caller_list_of_bounds ( _UNUSED_ entity  fun,
list  le 
)
static

return the list of bounds

of expression

of expression

Parameters
leof expression

Definition at line 133 of file compiler.c.

136 {
137  list /* of expression */ lneeded = NIL;
138  int len = gen_length(le);
139 
140  for (; len>=1; len--)
141  {
142  expression e = EXPRESSION(gen_nth(len-1, le));
143  syntax s = expression_syntax(e);
144 
145  if (syntax_reference_p(s))
146  {
147  entity var, old;
148 
150  var = load_new_node(old);
151  pips_debug(8, "considering %s\n", entity_name(var));
152 
153  if (array_distributed_p(old))
154  {
155  int dim = NumberOfDimension(var);
156 
157  for (; dim>=1; dim--)
158  {
159  if (ith_dim_overlapable_p(old, dim))
160  {
161  lneeded =
162  CONS(EXPRESSION, hpfc_array_bound(var, false, dim),
163  CONS(EXPRESSION, hpfc_array_bound(var, true, dim),
164  lneeded));
165  }
166  }
167  }
168  }
169  }
170 
171  return lneeded;
172 }
#define NIL
The empty list (nil in Lisp)
Definition: newgen_list.h:47
#define CONS(_t_, _i_, _l_)
List element cell constructor (insert an element at the beginning of a list)
Definition: newgen_list.h:150
gen_chunk gen_nth(int n, const list l)
to be used as ENTITY(gen_nth(3, l))...
Definition: list.c:710
bool ith_dim_overlapable_p(entity array, int i)
Definition: hpfc-util.c:178
entity load_new_node(entity)
expression hpfc_array_bound(entity, bool, int)
Definition: run-time.c:516
bool array_distributed_p(entity)
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145
int NumberOfDimension(entity)
Definition: size.c:588
#define syntax_reference_p(x)
Definition: ri.h:2728
#define syntax_reference(x)
Definition: ri.h:2730
#define reference_variable(x)
Definition: ri.h:2326
#define EXPRESSION(x)
EXPRESSION.
Definition: ri.h:1217
#define entity_name(x)
Definition: ri.h:2790
#define expression_syntax(x)
Definition: ri.h:1247
The structure used to build lists in NewGen.
Definition: newgen_list.h:41

References array_distributed_p(), CONS, entity_name, EXPRESSION, expression_syntax, gen_length(), gen_nth(), hpfc_array_bound(), ith_dim_overlapable_p(), load_new_node(), NIL, NumberOfDimension(), pips_debug, reference_variable, syntax_reference, and syntax_reference_p.

Referenced by hpf_compile_call().

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

◆ compile_control()

static void compile_control ( control  c,
statement_mapping  maph,
statement_mapping  mapn 
)
static

Definition at line 326 of file compiler.c.

330 {
331  control hostc, nodec;
332  statement stath, statn, statc = control_statement(c);
333 
334  hpf_compiler(statc, &stath, &statn);
335 
336  DEBUG_STAT(7, "statc", statc);
337  DEBUG_STAT(7, "host stat", stath);
338  DEBUG_STAT(7, "node stat", statn);
339 
340  hostc = make_control(stath, NIL, NIL);
341  SET_CONTROL_MAPPING(maph, c, hostc);
342 
343  nodec = make_control(statn, NIL, NIL);
344  SET_CONTROL_MAPPING(mapn, c, nodec);
345 }
control make_control(statement a1, list a2, list a3)
Definition: ri.c:523
void hpf_compiler(statement stat, statement *hoststatp, statement *nodestatp)
what: compile a statement into a host and SPMD node code.
Definition: compiler.c:710
#define DEBUG_STAT(D, W, S)
#define SET_CONTROL_MAPPING(map, cont, val)
Definition: newgen-local.h:86

References control_statement, DEBUG_STAT, hpf_compiler(), make_control(), NIL, and SET_CONTROL_MAPPING.

Referenced by hpf_compile_unstructured().

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

◆ hpf_compile_block()

static void hpf_compile_block ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

of statements

Definition at line 58 of file compiler.c.

61 {
62  list /* of statements */ lhost=NIL, lnode=NIL;
63  statement hostcd, nodecd;
64 
66 
67  (*hoststatp) = MakeStatementLike(stat, is_instruction_block);
68  (*nodestatp) = MakeStatementLike(stat, is_instruction_block);
69 
70  MAP(STATEMENT, s,
71  {
72  hpf_compiler(s,&hostcd,&nodecd);
73 
74  lhost = CONS(STATEMENT, hostcd, lhost);
75  lnode = CONS(STATEMENT, nodecd, lnode);
76  },
78 
81 
82  DEBUG_STAT(9, entity_name(host_module), *hoststatp);
83  DEBUG_STAT(9, entity_name(node_module), *nodestatp);
84 }
entity host_module
HPFC - Fabien Coelho, May 1993 and later...
Definition: compiler.c:47
entity node_module
Definition: compiler.c:47
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
#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
statement MakeStatementLike(statement stat, int the_tag)
creates a new statement for the given module that looks like the stat one, i.e.
Definition: hpfc-util.c:203
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define instruction_block_p(i)
#define is_instruction_block
soft block->sequence transition
#define instruction_block(i)
#define statement_instruction(x)
Definition: ri.h:2458
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413

References CONS, DEBUG_STAT, entity_name, gen_nreverse(), host_module, hpf_compiler(), instruction_block, instruction_block_p, is_instruction_block, MakeStatementLike(), MAP, NIL, node_module, pips_assert, STATEMENT, and statement_instruction.

Referenced by hpf_compiler().

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

◆ hpf_compile_call()

static void hpf_compile_call ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

returned node version

IO functions should be detected earlier, in hpf_compiler

"kill" FC directive. tells that the array is dead, hence all copies are live...

of statement

no reference to distributed arrays... the call is just translated into local objects.

should consider read and written variables

of expressions

C1-ALPHA

reductions are detected here. They are not handled otherwise

C1-BETA

call to something with distributed variables, which is not an assignment. Since I do not use the effects as I should, nothing is done...

temporary (?:-) hack

of expressions

Parameters
hoststatpcompiled statement
nodestatpreturned host version

Definition at line 175 of file compiler.c.

179 {
181 
182  /* IO functions should be detected earlier, in hpf_compiler
183  */
184  pips_assert("not an io call", !IO_CALL_P(c));
186  pips_debug(7, "function %s\n", entity_name(call_function(c)));
187 
188  DEBUG_STAT(9, "statement", stat);
189 
190  /* "kill" FC directive.
191  * tells that the array is dead, hence all copies are live...
192  */
194  {
195  list /* of statement */ ls = NIL;
196 
197  MAP(EXPRESSION, e,
198  {
199  entity primary = expression_to_entity(e);
200  pips_debug(5, "dealing with array %s\n", entity_name(primary));
201  if (array_distributed_p(primary))
202  ls = CONS(STATEMENT, generate_all_liveness(primary, true), ls);
203  },
204  call_arguments(c));
205 
206  (*hoststatp) = MakeStatementLike(stat, is_instruction_block);
207  (*nodestatp) = MakeStatementLike(stat, is_instruction_block);
208 
210  instruction_block(statement_instruction(*nodestatp)) = ls;
211 
212  return;
213  }
214 
215  /* no reference to distributed arrays...
216  * the call is just translated into local objects.
217  */
218  if (!ref_to_dist_array_p(c))
219  {
220  pips_debug(7, "no reference to distributed variable\n");
221 
222  (*hoststatp)=MakeStatementLike(stat, is_instruction_call);
223  (*nodestatp)=MakeStatementLike(stat, is_instruction_call);
224 
227 
230 
231  DEBUG_STAT(8, entity_name(host_module), *hoststatp);
232  DEBUG_STAT(8, entity_name(node_module), *nodestatp);
233 
234  return;
235  }
236 
237  /* should consider read and written variables
238  */
240  {
241  list /* of expressions */
242  lh = NIL, ln = NIL, args = call_arguments(c) ;
243  expression
244  w = EXPRESSION(CAR(args)),
245  r = EXPRESSION(CAR(CDR(args)));
246 
248 
251  {
252  pips_debug(8, "c1-alpha\n");
253 
254  generate_c1_alpha(stat, &lh, &ln); /* C1-ALPHA */
255  }
256  else
257  {
258  syntax s = expression_syntax(r);
259 
260  /* reductions are detected here. They are not handled otherwise
261  */
263  {
264  statement sh, sn;
265 
266  if (!compile_reduction(stat, &sh, &sn))
267  pips_internal_error("reduction compilation failed");
268 
269  lh = CONS(STATEMENT, sh, NIL);
270  ln = CONS(STATEMENT, sn, NIL);
271  }
272  else
273  {
274  pips_debug(8, "c1-beta\n");
275 
276  generate_c1_beta(stat, &lh, &ln); /* C1-BETA */
277  }
278  }
279 
280  (*hoststatp) = MakeStatementLike(stat, is_instruction_block);
281  (*nodestatp) = MakeStatementLike(stat, is_instruction_block);
282 
283  instruction_block(statement_instruction(*hoststatp)) = lh;
284  instruction_block(statement_instruction(*nodestatp)) = ln;
285 
286  DEBUG_STAT(8, entity_name(host_module), *hoststatp);
287  DEBUG_STAT(8, entity_name(node_module), *nodestatp);
288 
289  return;
290  }
291 
292  /* call to something with distributed variables, which is not an
293  * assignment. Since I do not use the effects as I should, nothing is
294  * done...
295  */
296 
297  /* temporary (?:-) hack
298  */
299  {
300  entity fun = call_function(c);
301  list /* of expressions */
302  args = call_arguments(c),
304  len=lUpdateExpr(node_module, args);
305 
306  update_overlaps_in_caller(fun, args);
307 
308  pips_debug(7, "some references to distributed variable\n");
309 
310  (*hoststatp)=MakeStatementLike(stat, is_instruction_call);
311  (*nodestatp)=MakeStatementLike(stat, is_instruction_call);
312 
314  make_call(fun, leh);
315 
317  make_call(fun, gen_nconc(len, caller_list_of_bounds(fun, args)));
318 
319  DEBUG_STAT(8, entity_name(host_module), *hoststatp);
320  DEBUG_STAT(8, entity_name(node_module), *nodestatp);
321 
322  return;
323  }
324 }
call make_call(entity a1, list a2)
Definition: ri.c:269
call copy_call(call p)
CALL.
Definition: ri.c:233
static list caller_list_of_bounds(_UNUSED_ entity fun, list le)
return the list of bounds
Definition: compiler.c:133
void generate_c1_beta(statement stat, list *lhp, list *lnp)
??? this should work (but that is not the case yet), with every call with no write to distributed arr...
Definition: generate.c:41
void generate_c1_alpha(statement stat, list *lhp, list *lnp)
generate_c1_alpha
Definition: generate.c:121
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
#define CAR(pcons)
Get the value of the first element of a list.
Definition: newgen_list.h:92
#define CDR(pcons)
Get the list less its first element.
Definition: newgen_list.h:111
void update_object_for_module(void *obj, entity module)
list lUpdateExpr(entity module, list l)
list lUpdateExpr_but_distributed(entity module, list l)
used for compiling calls.
bool ref_to_dist_array_p(void *obj)
this file describe a few functions usefull to the compiler to manage the hpfc data structures.
Definition: hpfc-util.c:48
void update_overlaps_in_caller(entity fun, list le)
the overlaps of the actual parameters are updated according to the formal requirements.
Definition: declarations.c:864
bool compile_reduction(statement, statement *, statement *)
bool compile_reduction(initial, phost, pnode)
statement generate_all_liveness(entity, bool)
Definition: remapping.c:940
bool call_reduction_p(call)
Definition: special_cases.c:87
#define pips_internal_error
Definition: misc-local.h:149
#define IO_CALL_P(call)
#define ENTITY_ASSIGN_P(e)
entity expression_to_entity(expression e)
just returns the entity of an expression, or entity_undefined
Definition: expression.c:3140
bool dead_fcd_directive_p(entity f)
Definition: hpfc.c:74
#define call_function(x)
Definition: ri.h:709
#define syntax_call_p(x)
Definition: ri.h:2734
@ is_instruction_call
Definition: ri.h:1474
#define syntax_call(x)
Definition: ri.h:2736
#define instruction_call_p(x)
Definition: ri.h:1527
#define instruction_call(x)
Definition: ri.h:1529
#define call_arguments(x)
Definition: ri.h:711

References array_distributed_p(), call_arguments, call_function, call_reduction_p(), caller_list_of_bounds(), CAR, CDR, compile_reduction(), CONS, copy_call(), dead_fcd_directive_p(), DEBUG_STAT, ENTITY_ASSIGN_P, entity_name, EXPRESSION, expression_syntax, expression_to_entity(), gen_nconc(), generate_all_liveness(), generate_c1_alpha(), generate_c1_beta(), host_module, instruction_block, instruction_call, instruction_call_p, IO_CALL_P, is_instruction_block, is_instruction_call, lUpdateExpr(), lUpdateExpr_but_distributed(), make_call(), MakeStatementLike(), MAP, NIL, node_module, pips_assert, pips_debug, pips_internal_error, ref_to_dist_array_p(), reference_variable, STATEMENT, statement_instruction, syntax_call, syntax_call_p, syntax_reference, syntax_reference_p, update_object_for_module(), and update_overlaps_in_caller().

Referenced by hpf_compiler().

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

◆ hpf_compile_loop()

static void hpf_compile_loop ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

should verify that only listed in labels and distributed entities are defined inside the body of the loop

Definition at line 623 of file compiler.c.

626 {
627  loop the_loop = instruction_loop(statement_instruction(stat));
628  list l = NIL;
629  entity var;
630  bool is_shift = subarray_shift_p(stat, &var, &l);
631 
632  pips_assert("stat is a loop", statement_loop_p(stat));
633 
634  if (is_shift)
635  {
636  pips_debug(4, "shift detected\n");
637 
638  *nodestatp = generate_subarray_shift(stat, var, l);
639  *hoststatp = make_empty_statement();
640  }
641  else if (execution_parallel_p(loop_execution(the_loop)))
642  {
643  reference left, right;
644  bool /* should verify that only listed in labels and distributed
645  * entities are defined inside the body of the loop
646  */
647  at_ac = atomic_accesses_only_p(stat),
648  in_in = indirections_inside_statement_p(stat),
649  is_full_copy = full_copy_p(stat, &left, &right);
650 
651  pips_debug(5, "condition results: aa %d, in %d\n", at_ac, in_in);
652 
653 
654  if (is_full_copy)
655  {
656  pips_debug(4, "full copy detected\n");
657 
658  *nodestatp = generate_full_copy(left, right);
659  *hoststatp = make_empty_statement();
660  }
661  else if (at_ac && !in_in)
662  {
663  statement overlapstat;
664 
665  pips_debug(7, "compiling a parallel loop\n");
666 
667  if (Overlap_Analysis(stat, &overlapstat))
668  {
669  string c = statement_comments(stat);
670  pips_debug(7, "overlap analysis succeeded\n");
671 
673  *nodestatp = overlapstat;
674  if (!string_undefined_p(c))
675  insert_comments_to_statement(*nodestatp, c);
676  }
677  else
678  {
679  pips_debug(7, "overlap analysis is not ok...\n");
680 
681  if (parallel_loop_in_stat_p(loop_body(the_loop)))
682  hpf_compile_sequential_loop(stat, hoststatp, nodestatp);
683  else
684  hpf_compile_parallel_loop(stat, hoststatp, nodestatp);
685  }
686  }
687  else
688  {
689  pips_debug(7, "compiling a parallel loop sequential...\n");
690  hpf_compile_sequential_loop(stat, hoststatp, nodestatp);
691  }
692  }
693  else
694  {
695  pips_debug(7,"compiling a sequential loop\n");
696 
697  hpf_compile_sequential_loop(stat, hoststatp, nodestatp);
698  }
699 }
bool indirections_inside_statement_p(_UNUSED_ statement stat)
indirections_inside_statement_p
bool atomic_accesses_only_p(_UNUSED_ statement stat)
atomic_accesses_only_p
static void hpf_compile_sequential_loop(statement stat, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:460
static bool parallel_loop_in_stat_p(statement s)
Definition: compiler.c:615
static void hpf_compile_parallel_loop(statement stat, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:551
bool statement_loop_p(statement)
Definition: statement.c:349
void insert_comments_to_statement(statement, const char *)
Insert a comment string (if non empty) at the beginning of the comments of a statement.
Definition: statement.c:1916
statement make_continue_statement(entity)
Definition: statement.c:953
bool full_copy_p(statement, reference *, reference *)
bool Overlap_Analysis(statement, statement *)
check conditions and compile...
Definition: o-analysis.c:870
bool subarray_shift_p(statement, entity *, list *)
statement generate_full_copy(reference, reference)
statement generate_full_copy(reference left, reference right)
statement generate_subarray_shift(statement, entity, list)
statement generate_subarray_shift(s, var, lshift) statement s; entity var; list lshift;
#define string_undefined_p(s)
Definition: newgen_types.h:41
#define make_empty_statement
An alias for make_empty_block_statement.
entity entity_empty_label(void)
Definition: entity.c:1105
#define loop_body(x)
Definition: ri.h:1644
#define loop_execution(x)
Definition: ri.h:1648
#define instruction_loop(x)
Definition: ri.h:1520
#define statement_comments(x)
Definition: ri.h:2456
#define execution_parallel_p(x)
Definition: ri.h:1211

References atomic_accesses_only_p(), entity_empty_label(), execution_parallel_p, full_copy_p(), generate_full_copy(), generate_subarray_shift(), hpf_compile_parallel_loop(), hpf_compile_sequential_loop(), indirections_inside_statement_p(), insert_comments_to_statement(), instruction_loop, loop_body, loop_execution, make_continue_statement(), make_empty_statement, NIL, Overlap_Analysis(), parallel_loop_in_stat_p(), pips_assert, pips_debug, statement_comments, statement_instruction, statement_loop_p(), string_undefined_p, and subarray_shift_p().

Referenced by hpf_compiler().

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

◆ hpf_compile_parallel_body()

static void hpf_compile_parallel_body ( statement  body,
statement hoststatp,
statement nodestatp 
)
static

??? dependances are not surely respected in the definitions list... should check that only locals variables, that are not replicated, may be defined during the body of the loop...

very partial

Definition at line 518 of file compiler.c.

520 {
521  list lw = NIL, lr = NIL, li = NIL, ls = NIL, lbs = NIL;
522 
523  /* ???
524  * dependances are not surely respected in the definitions list...
525  * should check that only locals variables, that are not replicated,
526  * may be defined during the body of the loop...
527  */
528  FindRefToDistArrayInStatement(body, &lw, &lr);
530  ls = FindDefinitionsOf(body, li);
531  gen_free_list(li), li=NIL;
532 
533  if (gen_length(lw)==0 && gen_length(lr)==0) /* very partial */
534  {
535  (*hoststatp) = copy_statement(body);
536  (*nodestatp) = copy_statement(body);
537  }
538  else
539  {
540  generate_parallel_body(body, &lbs, lw, lr);
541 
542  (*hoststatp) = NULL;
543  (*nodestatp) = make_block_statement(gen_nconc(ls, lbs));
544  }
545 
546  gen_free_list(lw), lw=NIL;
547  gen_free_list(lr), lr=NIL;
548 }
statement copy_statement(statement p)
STATEMENT.
Definition: ri.c:2186
list lIndicesOfRef(list lsyn)
computes the list of indices of the list of ref that are variables...
void FindRefToDistArrayInStatement(statement obj, list *lwp, list *lrp)
list FindDefinitionsOf(statement stat, list lsyn)
list AddOnceToIndicesList(list l, list lsyn)
void generate_parallel_body(statement body, list *lstatp, list lw, list lr)
Definition: generate.c:511
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327

References AddOnceToIndicesList(), copy_statement(), FindDefinitionsOf(), FindRefToDistArrayInStatement(), gen_free_list(), gen_length(), gen_nconc(), generate_parallel_body(), lIndicesOfRef(), make_block_statement(), and NIL.

Referenced by hpf_compile_parallel_loop().

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

◆ hpf_compile_parallel_loop()

static void hpf_compile_parallel_loop ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

Definition at line 551 of file compiler.c.

555 {
556  loop the_loop = statement_loop(stat);
557  statement s, nodebody, body = loop_body(the_loop);
558  instruction bodyinst = statement_instruction(body);
559  entity
560  label = loop_label(the_loop),
561  index = loop_index(the_loop),
562  nindex = NewVariableForModule(node_module,index);
563  range r = loop_range(the_loop);
564  expression
565  lower = range_lower(r),
566  upper = range_upper(r),
567  increment = range_increment(r);
568  list lw=NIL, lr=NIL;
569 
570  FindRefToDistArrayInStatement(stat, &lw, &lr);
571 
572  if (lw||lr)
573  {
574  pips_assert("parallel loop",
576 
577  if ((instruction_loop_p(bodyinst)) &&
579  hpf_compile_parallel_loop(body, &s, &nodebody);
580  else
581  hpf_compile_parallel_body(body, &s, &nodebody);
582 
584  (*nodestatp) = MakeStatementLike(stat, is_instruction_loop);
585 
587  make_loop(nindex,
591  nodebody,
592  label,
594  NULL);
595  } else {
596  (*hoststatp) = copy_statement(stat);
597  (*nodestatp) = copy_statement(stat);
598  }
599 
600  gen_free_list(lw), gen_free_list(lr);
601 
602 }
execution make_execution(enum execution_utype tag, void *val)
Definition: ri.c:838
loop make_loop(entity a1, range a2, statement a3, entity a4, execution a5, list a6)
Definition: ri.c:1301
range make_range(expression a1, expression a2, expression a3)
Definition: ri.c:2041
static void hpf_compile_parallel_body(statement body, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:518
loop statement_loop(statement)
Get the loop of a statement.
Definition: statement.c:1374
entity NewVariableForModule(entity module, entity e)
expression UpdateExpressionForModule(entity module, expression ex)
this function creates a new expression using the mapping of old to new variables map.
#define UU
Definition: newgen_types.h:98
#define instruction_loop_p(x)
Definition: ri.h:1518
#define range_upper(x)
Definition: ri.h:2290
#define range_increment(x)
Definition: ri.h:2292
#define entity_undefined
Definition: ri.h:2761
@ is_instruction_loop
Definition: ri.h:1471
#define loop_label(x)
Definition: ri.h:1646
#define range_lower(x)
Definition: ri.h:2288
#define loop_range(x)
Definition: ri.h:1642
@ is_execution_sequential
Definition: ri.h:1189
#define loop_index(x)
Definition: ri.h:1640

References copy_statement(), entity_undefined, execution_parallel_p, FindRefToDistArrayInStatement(), gen_free_list(), hpf_compile_parallel_body(), instruction_loop, instruction_loop_p, is_execution_sequential, is_instruction_loop, loop_body, loop_execution, loop_index, loop_label, loop_range, make_continue_statement(), make_execution(), make_loop(), make_range(), MakeStatementLike(), NewVariableForModule(), NIL, node_module, pips_assert, range_increment, range_lower, range_upper, statement_instruction, statement_loop(), UpdateExpressionForModule(), and UU.

Referenced by hpf_compile_loop().

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

◆ hpf_compile_sequential_loop()

static void hpf_compile_sequential_loop ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

of entities

??? memory leak, hostbody is lost whatever it was.

Definition at line 460 of file compiler.c.

462 {
463  loop the_loop=statement_loop(stat);
464  statement body = loop_body(the_loop), hostbody, nodebody;
465  range r=loop_range(the_loop);
466  list /* of entities */ locals=loop_locals(the_loop);
467  entity
468  label = loop_label(the_loop),
469  index = loop_index(the_loop),
470  nindex = NewVariableForModule(node_module, index),
471  hindex = NewVariableForModule(host_module, index);
472  expression
473  lower = range_lower(r),
474  upper = range_upper(r),
475  increment = range_increment(r);
476 
477  hpf_compiler(body, &hostbody, &nodebody);
478 
479  if (empty_code_p(hostbody))
480  {
481  /* ??? memory leak, hostbody is lost whatever it was.
482  */
484  }
485  else
486  {
487  (*hoststatp)=MakeStatementLike(stat, is_instruction_loop);
488 
490  make_loop(hindex,
494  hostbody,
495  label,
498  }
499 
500  DEBUG_STAT(8, "host stat", *hoststatp);
501 
502  (*nodestatp)=MakeStatementLike(stat, is_instruction_loop);
503 
505  make_loop(nindex,
509  nodebody,
510  label,
513 
514  DEBUG_STAT(8, "node stat", *nodestatp);
515 }
bool empty_code_p(statement)
statement.c
Definition: statement.c:86
list lNewVariableForModule(entity module, list le)
#define loop_locals(x)
Definition: ri.h:1650

References DEBUG_STAT, empty_code_p(), entity_undefined, host_module, hpf_compiler(), instruction_loop, is_execution_sequential, is_instruction_loop, lNewVariableForModule(), loop_body, loop_index, loop_label, loop_locals, loop_range, make_continue_statement(), make_execution(), make_loop(), make_range(), MakeStatementLike(), NewVariableForModule(), node_module, range_increment, range_lower, range_upper, statement_instruction, statement_loop(), UpdateExpressionForModule(), and UU.

Referenced by hpf_compile_loop().

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

◆ hpf_compile_test()

static void hpf_compile_test ( statement  s,
statement hoststatp,
statement nodestatp 
)
static

if it may happen that a condition modifies the value of a distributed variable, this condition is to be put out of the statement, for separate compilation.

Definition at line 87 of file compiler.c.

90 {
91  statement
92  s_true, s_hosttrue, s_nodetrue,
93  s_false, s_hostfalse, s_nodefalse;
94  test the_test;
95  expression condition;
96 
98 
100  condition = test_condition(the_test);
101 
102  (*hoststatp) = MakeStatementLike(s, is_instruction_test);
103  (*nodestatp) = MakeStatementLike(s, is_instruction_test);
104 
105  /* if it may happen that a condition modifies the value
106  * of a distributed variable, this condition is to be
107  * put out of the statement, for separate compilation.
108  */
109 
110  s_true = test_true(the_test);
111  s_false = test_false(the_test);
112 
113  hpf_compiler(s_true, &s_hosttrue, &s_nodetrue);
114  hpf_compiler(s_false, &s_hostfalse, &s_nodefalse);
115 
118  s_hosttrue,
119  s_hostfalse);
120 
123  s_nodetrue,
124  s_nodefalse);
125 
126  DEBUG_STAT(9, entity_name(host_module), *hoststatp);
127  DEBUG_STAT(9, entity_name(node_module), *nodestatp);
128 }
test make_test(expression a1, statement a2, statement a3)
Definition: ri.c:2607
#define test_false(x)
Definition: ri.h:2837
@ is_instruction_test
Definition: ri.h:1470
#define test_true(x)
Definition: ri.h:2835
#define test_condition(x)
Definition: ri.h:2833
#define instruction_test_p(x)
Definition: ri.h:1515
#define instruction_test(x)
Definition: ri.h:1517

References DEBUG_STAT, entity_name, host_module, hpf_compiler(), instruction_test, instruction_test_p, is_instruction_test, make_test(), MakeStatementLike(), node_module, pips_assert, statement_instruction, test_condition, test_false, test_true, and UpdateExpressionForModule().

Referenced by hpf_compiler().

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

◆ hpf_compile_unstructured()

static void hpf_compile_unstructured ( statement  stat,
statement hoststatp,
statement nodestatp 
)
static

nothing spacial is done! ??? there may be a problem with the label of the statement, if any.

HOST statement

NODE statement

Definition at line 348 of file compiler.c.

352 {
354 
355  pips_assert("unstructured", instruction_unstructured_p(inst));
356 
358  {
359  pips_debug(7, "one statement recognize\n");
360 
361  /* nothing spacial is done!
362  * ??? there may be a problem with the label of the statement, if any.
363  */
366  hoststatp, nodestatp);
367  }
368  else
369  {
371  hostmap = MAKE_CONTROL_MAPPING(),
372  nodemap = MAKE_CONTROL_MAPPING();
375  ce = unstructured_exit(u), new_ct, new_ce;
376  list blocks = NIL;
377 
378  pips_debug(6, "beginning\n");
379 
380  CONTROL_MAP(c, compile_control(c, hostmap, nodemap), ct, blocks);
381 
382  if (!gen_in_list_p(ce, blocks))
383  {
384  pips_debug(5, "exit not in blocks\n");
385  blocks = CONS(CONTROL, ce, blocks);
386  compile_control(ce, hostmap, nodemap);
387  }
388 
389  MAP(CONTROL, c,
390  {
391  update_control_lists(c, hostmap);
392  update_control_lists(c, nodemap);
393  },
394  blocks);
395 
396  ifdebug(9)
397  {
398  control h_tmp, n_tmp;
399 
400  pips_debug(9, "controls:\n");
401 
402  MAP(CONTROL, c_tmp,
403  {
404  h_tmp = (control) GET_CONTROL_MAPPING(hostmap, c_tmp);
405  n_tmp = (control) GET_CONTROL_MAPPING(nodemap, c_tmp);
406 
407  debug_print_control(c_tmp, "initial");
408  debug_print_control(h_tmp, "host");
409  debug_print_control(n_tmp, "node");
410  },
411  blocks);
412  }
413 
414  /* HOST statement
415  */
416  (*hoststatp) = MakeStatementLike(stat, is_instruction_unstructured);
417 
418  new_ct = (control) GET_CONTROL_MAPPING(hostmap, ct);
419  new_ce = (control) GET_CONTROL_MAPPING(hostmap, ce);
420 
421  pips_assert("defined control", !control_undefined_p(new_ct) &&
422  !control_undefined_p(new_ce));
423 
424  ifdebug(9)
425  {
426  pips_debug(9, "host controls for [%p,%p]:\n", ct, ce);
427 
428  debug_print_control(new_ct, "main");
429  debug_print_control(new_ce, "exit");
430  }
431 
433  make_unstructured(new_ct, new_ce);
434 
435  DEBUG_STAT(7, "host new stat", *hoststatp);
436 
437  /* NODE statement
438  */
439  (*nodestatp) = MakeStatementLike(stat, is_instruction_unstructured);
440 
441  new_ct = (control) GET_CONTROL_MAPPING(nodemap, ct);
442  new_ce = (control) GET_CONTROL_MAPPING(nodemap, ce);
443 
444  pips_assert("defined control",
445  !control_undefined_p(new_ct) &&
446  !control_undefined_p(new_ce));
447 
449  make_unstructured(new_ct, new_ce);
450 
451  DEBUG_STAT(7, "host new stat (again)", *hoststatp);
452 
454  FREE_CONTROL_MAPPING(hostmap);
455  FREE_CONTROL_MAPPING(nodemap);
456  }
457 }
unstructured make_unstructured(control a1, control a2)
Definition: ri.c:2778
static list blocks
lisp of loops
void update_control_lists(control c, control_mapping map)
Compiler Utilities.
Definition: compiler-util.c:36
#define debug_print_control(c, w)
Definition: compiler.c:49
static void compile_control(control c, statement_mapping maph, statement_mapping mapn)
Definition: compiler.c:326
#define CONTROL_MAP(ctl, code, c, list)
Macro to walk through all the controls reachable from a given control node of an unstructured.
bool gen_in_list_p(const void *vo, const list lx)
tell whether vo belongs to lx
Definition: list.c:734
#define one_statement_unstructured(u)
Definition: defines-local.h:92
struct _newgen_struct_control_ * control
#define MAKE_CONTROL_MAPPING()
Definition: newgen-local.h:82
#define GET_CONTROL_MAPPING(map, cont)
Definition: newgen-local.h:88
#define FREE_CONTROL_MAPPING(map)
Definition: newgen-local.h:84
#define unstructured_control
After the modification in Newgen: unstructured = entry:control x exit:control we have create a macro ...
#define CONTROL(x)
CONTROL.
Definition: ri.h:910
@ is_instruction_unstructured
Definition: ri.h:1475
#define control_undefined_p(x)
Definition: ri.h:917
#define unstructured_exit(x)
Definition: ri.h:3006
#define instruction_unstructured_p(x)
Definition: ri.h:1530
#define instruction_unstructured(x)
Definition: ri.h:1532
#define ifdebug(n)
Definition: sg.c:47

References blocks, compile_control(), CONS, CONTROL, CONTROL_MAP, control_statement, control_undefined_p, debug_print_control, DEBUG_STAT, FREE_CONTROL_MAPPING, gen_free_list(), gen_in_list_p(), GET_CONTROL_MAPPING, hpf_compiler(), ifdebug, instruction_unstructured, instruction_unstructured_p, is_instruction_unstructured, MAKE_CONTROL_MAPPING, make_unstructured(), MakeStatementLike(), MAP, NIL, one_statement_unstructured, pips_assert, pips_debug, statement_instruction, unstructured_control, unstructured_exit, and update_control_lists().

Referenced by hpf_compiler().

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

◆ hpf_compiler()

void hpf_compiler ( statement  stat,
statement hoststatp,
statement nodestatp 
)

what: compile a statement into a host and SPMD node code.

how: double code rewriting in a recursive traversal of stat. input: statement stat. output: statements *hoststatp and *nodestatp side effects: ? bugs or features:

  • special care is made here of I/O and remappings.

of hpfc_reduction

necessary

remapping

HPF REDUCTION

else usual stuff

of statement

Parameters
stattat
hoststatpoststatp
nodestatpodestatp

Definition at line 710 of file compiler.c.

714 {
715  list /* of hpfc_reduction */ lr = NIL;
716  bool root_statement_p = stat==get_current_module_statement();
717 
718  DEBUG_STAT(9, "stat is", stat);
719  pips_debug(9, "only io %d, remapping %d, reduction %d\n",
721  bound_renamings_p(stat),
722  bound_hpf_reductions_p(stat));
723 
724  if (load_statement_only_io(stat)==1) /* necessary */
725  {
726  io_efficient_compile(stat, hoststatp, nodestatp);
727  return;
728  }
729  else if (bound_renamings_p(stat) && !root_statement_p) /* remapping */
730  {
731  remapping_compile(stat, hoststatp, nodestatp);
732  return;
733  }
734 
735  if (bound_hpf_reductions_p(stat)) /* HPF REDUCTION */
736  lr = handle_hpf_reduction(stat);
737 
738  /* else usual stuff
739  */
741  {
743  hpf_compile_block(stat, hoststatp, nodestatp);
744  break;
745  case is_instruction_test:
746  hpf_compile_test(stat, hoststatp, nodestatp);
747  break;
748  case is_instruction_loop:
749  hpf_compile_loop(stat, hoststatp, nodestatp);
750  break;
751  case is_instruction_call:
752  hpf_compile_call(stat, hoststatp, nodestatp);
753  break;
755  hpf_compile_unstructured(stat, hoststatp, nodestatp);
756  break;
757  case is_instruction_goto:
758  default:
759  pips_internal_error("unexpected instruction tag");
760  break;
761  }
762 
763  if (lr)
764  {
765  list /* of statement */ lh, ln;
766  lh = gen_nconc(compile_hpf_reduction(lr, true, true),
767  CONS(STATEMENT, *hoststatp,
768  compile_hpf_reduction(lr, false, true)));
769  ln = gen_nconc(compile_hpf_reduction(lr, true, false),
770  CONS(STATEMENT, *nodestatp,
771  compile_hpf_reduction(lr, false, false)));
772 
773  *hoststatp = make_block_statement(lh);
774  *nodestatp = make_block_statement(ln);
775  }
776 
777  if (root_statement_p && bound_renamings_p(stat))
778  {
779  *nodestatp = make_block_statement(
781  CONS(STATEMENT, *nodestatp, NIL)));
782  }
783 }
static void hpf_compile_loop(statement stat, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:623
static void hpf_compile_call(statement stat, statement *hoststatp, statement *nodestatp)
returned node version
Definition: compiler.c:175
static void hpf_compile_unstructured(statement stat, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:348
static void hpf_compile_test(statement s, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:87
static void hpf_compile_block(statement stat, statement *hoststatp, statement *nodestatp)
Definition: compiler.c:58
statement get_current_module_statement(void)
Get the current module statement.
Definition: static.c:208
void remapping_compile(statement, statement *, statement *)
void remapping_compile(s, hsp, nsp) statement s, *hsp, *nsp;
Definition: remapping.c:1302
bool bound_hpf_reductions_p(statement)
bool bound_renamings_p(statement)
statement root_statement_remapping_inits(statement)
returns the initialization statement: must initialize the status and liveness of arrays
Definition: remapping.c:1265
void io_efficient_compile(statement, statement *, statement *)
compile an io statement
Definition: io-compile.c:911
list compile_hpf_reduction(list, bool, bool)
of statement
list handle_hpf_reduction(statement)
of hpfc_reductions
bool load_statement_only_io(statement)
@ is_instruction_goto
Definition: ri.h:1473
#define instruction_tag(x)
Definition: ri.h:1511

References bound_hpf_reductions_p(), bound_renamings_p(), compile_hpf_reduction(), CONS, DEBUG_STAT, gen_nconc(), get_current_module_statement(), handle_hpf_reduction(), hpf_compile_block(), hpf_compile_call(), hpf_compile_loop(), hpf_compile_test(), hpf_compile_unstructured(), instruction_tag, io_efficient_compile(), is_instruction_block, is_instruction_call, is_instruction_goto, is_instruction_loop, is_instruction_test, is_instruction_unstructured, load_statement_only_io(), make_block_statement(), NIL, pips_debug, pips_internal_error, remapping_compile(), root_statement_remapping_inits(), STATEMENT, and statement_instruction.

Referenced by compile_control(), compile_module(), hpf_compile_block(), hpf_compile_sequential_loop(), hpf_compile_test(), and hpf_compile_unstructured().

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

◆ loop_flt()

static bool loop_flt ( loop  l)
static

Definition at line 607 of file compiler.c.

608 {
610  parallel_loop_found = true;
611  gen_recurse_stop(NULL);
612  }
613  return !parallel_loop_found;
614 }
static bool parallel_loop_found
is there a parallel loop down s?
Definition: compiler.c:606
void gen_recurse_stop(void *obj)
Tells the recursion not to go in this object.
Definition: genClib.c:3251

References execution_parallel_p, gen_recurse_stop(), loop_execution, and parallel_loop_found.

Referenced by parallel_loop_in_stat_p().

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

◆ parallel_loop_in_stat_p()

static bool parallel_loop_in_stat_p ( statement  s)
static

Definition at line 615 of file compiler.c.

616 {
617  parallel_loop_found = false;
619  return parallel_loop_found;
620 }
static bool loop_flt(loop l)
Definition: compiler.c:607
#define gen_recurse(start, domain_number, flt, rwt)
Definition: genC.h:283
void gen_null(__attribute__((unused)) void *unused)
Ignore the argument.
Definition: genClib.c:2752
#define loop_domain
newgen_language_domain_defined
Definition: ri.h:218

References gen_null(), gen_recurse, loop_domain, loop_flt(), and parallel_loop_found.

Referenced by hpf_compile_loop().

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

Variable Documentation

◆ host_module

entity host_module

HPFC - Fabien Coelho, May 1993 and later...

compiler.c

Compiler

stat is the current statement to be compiled, and there are pointers to the current statement building of the node and host codes. the module of these are also kept in order to add the needed declarations generated by the compilation.

however, every entities of the compiled program, and of both generated programs will be mixed, due to the tabulated nature of these objects. some objects will be shared. I don't think this is a problem. global variables

Definition at line 47 of file compiler.c.

Referenced by add_declaration_to_host_and_link(), AddCommonToHostAndNodeModules(), AddEntityToHostAndNodeModules(), compile_module(), generate_c1_beta(), generate_read_of_ref_for_all(), hpf_compile_block(), hpf_compile_call(), hpf_compile_sequential_loop(), hpf_compile_test(), hpfc_common_hook(), hpfc_module_suffix(), init_host_and_node_entities(), NewVariableForModule(), old_name(), put_generated_resources_for_common(), put_generated_resources_for_module(), and update_object_for_module().

◆ node_module

◆ parallel_loop_found

bool parallel_loop_found
static

is there a parallel loop down s?

Definition at line 606 of file compiler.c.

Referenced by loop_flt(), and parallel_loop_in_stat_p().