PIPS
loop_unroll.c
Go to the documentation of this file.
1 /*
2 
3  $Id: loop_unroll.c 23495 2018-10-24 09:19:47Z coelho $
4 
5  Copyright 1989-2016 MINES ParisTech
6 
7  This file is part of PIPS.
8 
9  PIPS is free software: you can redistribute it and/or modify it
10  under the terms of the GNU General Public License as published by
11  the Free Software Foundation, either version 3 of the License, or
12  any later version.
13 
14  PIPS is distributed in the hope that it will be useful, but WITHOUT ANY
15  WARRANTY; without even the implied warranty of MERCHANTABILITY or
16  FITNESS FOR A PARTICULAR PURPOSE.
17 
18  See the GNU General Public License for more details.
19 
20  You should have received a copy of the GNU General Public License
21  along with PIPS. If not, see <http://www.gnu.org/licenses/>.
22 
23 */
24 
25 // this pass is used directly from sac, flatten_code...
26 
27 #ifdef HAVE_CONFIG_H
28  #include "pips_config.h"
29 #endif
30 /*
31 
32  LOOP_UNROLL()
33 
34  Bruno Baron, Francois Irigoin
35 */
36 #include <stdio.h>
37 #include <string.h>
38 
39 #include "genC.h"
40 #include "linear.h"
41 
42 #include "misc.h"
43 #include "properties.h"
44 #include "pipsdbm.h"
45 
46 #include "ri.h"
47 #include "ri-util.h"
48 #include "prettyprint.h" // for debugging
49 #include "text-util.h" // print_text
50 
51 #include "control.h" // clean_up_sequences, module_reorder
52 #include "transformations.h" // find_loop_from_label in "index_set_splitting.c"
53 
54 #define NORMALIZED_UPPER_BOUND_NAME "LU_NUB"
55 #define INTERMEDIATE_BOUND_NAME "LU_IB"
56 #define INDEX_NAME "LU_IND"
57 
59 {
60  pips_assert("input is integer", basic_int_p(b));
61  if(basic_int(b) > 10 && basic_int(b) < 20)
62  basic_int(b) -= 10;
63  return b;
64 }
65 
66 /* db_get_current_module_name() unusable because module not set,
67  * and setting it causes previous current module to be closed!
68  */
69 /* static string current_module_name = NULL; */
70 
71 
72 /* This function unrolls DO loop by a constant factor "rate" if their
73  * increment is statically known equal to 1. The initial loop is
74  * replaced by one unrolled loop followed by an epilogue loop:
75  *
76  * DO I= LOW, UP
77  *
78  * becomes
79  *
80  * DO I = LOW, LOW + RATE * (UP-LOW+1)/RATE -1, RATE
81  *
82  * DO I = LOW+ RATE * (UP-LOW+1)/RATE, UP
83  *
84  * where (UP+LOW-1)/RATE is the number of iteration of the unrolled
85  * loop.
86  *
87  * The initial index is reused to preserve as much readability as
88  * possible. The loop bounds are not simplified. This is left to other
89  * PIPS passes. Partial_eval can (hopefully) simplify the bounds and
90  * suppress_dead_code can eliminate the epilogue loop.
91  *
92  * The upper and lower loop bound expressions are assumed side-effects
93  * free.
94  */
95 static void do_loop_unroll_with_epilogue(statement loop_statement,
96  int rate,
97  void (*statement_post_processor)(statement))
98 {
99  loop il = instruction_loop(statement_instruction(loop_statement));
100  range lr = loop_range(il);
101  entity ind = loop_index(il);
102  //basic indb = variable_basic(type_variable(ultimate_type(entity_type(ind))));
103  expression low = range_lower(lr),
104  up = range_upper(lr);
105  //inc = range_increment(lr);
106  //entity nub, ib, lu_ind;
107  //expression rhs_expr, expr;
108  //entity label_entity;
110  statement loop_stmt1 = statement_undefined; // stmt for loop 1,
111  // unrolled loop
112  statement loop_stmt2 = statement_undefined; // stmt for loop 2, epilogue
114  range rg1 = range_undefined;
115  //range rg2 = range_undefined;
116  execution e = loop_execution(il);
117  //intptr_t lbval, ubval, incval;
118  //bool numeric_range_p = false;
119 
120  /* get rid of labels in loop body */
121  (void) clear_labels (loop_body (il));
122 
123  /* Instruction block is created and will contain the two new loops */
125 
126  /* compute the new intermediate loop bounds, nlow and nup=nlow-1 */
127  /* span = up-low+1 */
130  copy_expression(up),
131  copy_expression(low) ),
132  int_to_expression(1));
133  /* count = span/rate */
135  span,
136  int_to_expression(rate));
137  /* nlow = low + rate*count */
138  expression nlow =
140  copy_expression(low),
142  int_to_expression(rate),
143  count));
144  /* nup = nlow -1 */
146  copy_expression(nlow),
147  int_to_expression(1));
148 
149  /* The first statement gets the label of the initial loop */
150  // This should be postponed and added if necessary to loop_stmt1
151  //statement_label(stmt) = statement_label(loop_statement);
152  //statement_label(loop_statement) = entity_empty_label();
153  //instruction_block(block) = CONS(STATEMENT, stmt, NIL);
154 
155 
156  //instruction_block(block)= gen_nconc(instruction_block(block),
157  //CONS(STATEMENT,
158  //instruction_to_statement(inst),
159  //NIL ));
160 
161  /* The unrolled loop is generated first:
162  *
163  * DO I = low, nup, rate
164  * BODY(I\‍(I + 0))
165  * BODY(I\‍((I + 1))
166  * ...
167  * BODY(I\‍(I+(rate-1)))
168  * ENDDO
169  */
170  /* First, the loop range is generated */
171  rg1 = make_range(copy_expression(low),
172  nup,
173  int_to_expression(rate));
174 
175  /* Create body of the loop, with updated index */
177  //label_entity = make_new_label(get_current_module_name());
178  //instruction_block(statement_instruction(body)) =
179  // CONS(STATEMENT, make_continue_statement(label_entity), NIL);
180  int crate = rate; // FI: I hate modifications of a formal parameter
181  // because the stack is kind of corrupted when you debug
182  while(--crate>=0) {
183  /* Last transformated old loop added first */
184  //expression tmp_expr;
185  statement transformed_stmt;
186  list body_block = instruction_block(statement_instruction(body));
187 
191  NIL,
193  transformed_stmt = clone_statement(loop_body(il), cc);
194  free_clone_context(cc);
195 
196  ifdebug(9)
197  pips_assert("the cloned body is consistent",
198  statement_consistent_p(transformed_stmt));
199 
200  // If useful, modify the references to the loop index "ind"
201  if(crate>0) {
203  make_ref_expr(ind, NIL),
204  int_to_expression(crate));
205  ifdebug(9) {
206  pips_assert("The expression for the initial index is consistent",
208  }
209  /* FI: beware of dependent types? 31/10/2014 */
210  replace_entity_by_expression(transformed_stmt,ind,expr);
211 
212  ifdebug(9) {
213  pips_assert("The new loop body is consistent after index substitution",
214  statement_consistent_p(transformed_stmt));
215  }
216  free_expression(expr);
217 
218  ifdebug(9) {
219  pips_assert("Still true when expr is freed",
220  statement_consistent_p(transformed_stmt));
221  }
222  }
223  if(statement_post_processor)
224  statement_post_processor(transformed_stmt);
225 
226 
227  /* Add the transformated old loop body (transformed_stmt) at
228  * the begining of the loop
229  *
230  * For C code, be careful with local declarations and initializations
231  */
232  if( get_bool_property("LOOP_UNROLL_MERGE")
233  && instruction_block_p(statement_instruction(transformed_stmt)) ) {
234  if(ENDP(statement_declarations(body)))
235  statement_declarations(body)=statement_declarations(transformed_stmt);
236  else {
237  list declaration_initializations = NIL;
238  FOREACH(ENTITY,e,statement_declarations(transformed_stmt))
239  {
240  value v = entity_initial(e);
241  if( value_expression_p(v) )
242  {
243  statement s =
246  declaration_initializations =
247  CONS(STATEMENT,s,declaration_initializations);
248  }
249  }
250  declaration_initializations=gen_nreverse(declaration_initializations);
251  instruction_block(statement_instruction(transformed_stmt))=
252  gen_nconc(declaration_initializations,
253  instruction_block(statement_instruction(transformed_stmt)));
254  }
257  instruction_block(statement_instruction(transformed_stmt)));
258  }
259  else {
261  CONS(STATEMENT, transformed_stmt, body_block);
262  }
263  }
264 
265  /* Create loop and insert it in the top block */
266  /* ?? Should execution be the same as initial loop? */
268  make_loop(ind,
269  rg1,
270  body,
272  copy_execution(e),
273  NIL));
274 
275  ifdebug(9) {
276  pips_assert("the unrolled loop inst is consistent",
277  instruction_consistent_p(loop_inst1));
278  }
279 
280 
281  loop_stmt1 = instruction_to_statement(loop_inst1);
282  statement_label(loop_stmt1)=statement_label(loop_statement);
283  statement_label(loop_statement)=entity_empty_label();
285  CONS(STATEMENT, loop_stmt1, NIL));
286 
287  /* The epilogue loop is generated last:
288  *
289  * DO I = nlow, up
290  * BODY(I)
291  * ENDDO
292  */
293  loop_stmt2 = make_new_loop_statement(ind,
294  nlow,
295  copy_expression(up),
297  loop_body(il),
298  copy_execution(e));
300  CONS(STATEMENT, loop_stmt2, NIL));
301 
302  /* Free old instruction and replace with block */
303  /* FI: according to me, gen_copy_tree() does not create a copy sharing nothing
304  * with its actual parameter; if the free is executed, Pvecteur normalized_linear
305  * is destroyed (18 January 1993) */
306  /* gen_free(statement_instruction(loop_statement)); */
307  statement_instruction(loop_statement) = block;
308  /* Do not forget to move forbidden information associated with
309  block: */
310  fix_sequence_statement_attributes(loop_statement);
311 
312  ifdebug(9) {
313  print_statement(loop_statement);
314  pips_assert("the unrolled code is consistent",
315  statement_consistent_p(loop_statement));
316  }
317 
318  ifdebug(7) {
319  /* Stop debug in Newgen */
321  }
322 
323  pips_debug(3, "done\n");
324 }
325 
326 /* This function unrolls any DO loop by a constant factor "rate". If
327  the iteration count n cannot statically determined to be a multiple
328  of "rate", a first loop executes modulo(n,rate) iterations and then
329  a second loop contains the unrolled body. To cope with all posible
330  combinations of bounds and increments, the iteration count "n" is
331  computed according to Fortran standard and the new iterations are
332  numbered from 0 to n-1. The initial loop index is replaced by the
333  proper expressions. The generated code is general. It must be
334  simplified with passes partial_eval and/or suppress dead_code.
335 
336  Khadija Imadoueddine experienced a slowdown with this unrolling
337  scheme. She claims that it is due to the prologue loop which leads
338  to unaligned accesses in the unrolled loop when the arrays accessed
339  are aligned and accessed from the first element to the last.
340  */
341 static void do_loop_unroll_with_prologue(statement loop_statement,
342  int rate,
343  void (*statement_post_processor)(statement))
344 {
345  loop il = instruction_loop(statement_instruction(loop_statement));
346  range lr = loop_range(il);
347  entity ind = loop_index(il);
349  expression lb = range_lower(lr),
350  ub = range_upper(lr),
351  inc = range_increment(lr);
352  entity nub, ib, lu_ind;
353  expression rhs_expr, expr;
354  entity label_entity;
355  statement body, stmt;
356  instruction block, inst;
357  range rg;
358  intptr_t lbval, ubval, incval;
359  bool numeric_range_p = false;
360 
361  ifdebug(7) {
362  /* Start debug in Newgen */
364  }
365 
366  /* Validity of transformation should be checked */
367  /* ie.: - no side effects in replicated expressions */
368 
369  /* get rid of labels in loop body */
370  (void) clear_labels (loop_body (il));
371 
372  /* Instruction block is created and will contain everything */
374 
375 
376  /* Entity LU_NUB is created as well as its initializing
377  * statement. It contains the number of iterations according to
378  * Fortran standard:
379  *
380  * LU_NUB = ((UB - LB) + INC)/INC
381  *
382  * This should be OK with C for loops equivalent to a Fortran DO
383  * loop.
384  *
385  * Warning: basic must be signed becuase LU_NUB may be negative
386  *
387  * FI: Loop Unrolled New Upper Bound? In this code generation scheme
388  * the new lower bound is 0.
389  */
393  /* MakeBasic(is_basic_int)*/);
395 
396  if (expression_integer_value(lb, &lbval)
397  && expression_integer_value(ub, &ubval)
398  && expression_integer_value(inc, &incval)) {
399  numeric_range_p = true;
400  pips_assert("The loop increment is not zero", incval != 0);
401  rhs_expr = int_to_expression(FORTRAN_DIV(ubval-lbval+incval, incval));
402  }
403  else {
406  copy_expression(ub),
407  copy_expression(lb) ),
408  copy_expression(inc) );
410  expr,
411  copy_expression(inc) );
412  }
413  expr = make_ref_expr(nub, NIL);
415  rhs_expr );
416  ifdebug(9) {
417  pips_assert("The expression for the number of iterations is consistent",
419  }
420 
421  /* The first statement gets the label of the initial loop */
422  statement_label(stmt) = statement_label(loop_statement);
423  statement_label(loop_statement) = entity_empty_label();
425 
426 
427  /* Entity LU_IB is created with its initializing statement
428  *
429  * LU_IB = MOD(LU_NUB, rate)
430  *
431  * and it is appended to the block
432  *
433  * FI: Loop Unrolled Intermediate Bound?
434  */
437  copy_basic(indb)
438  /* MakeBasic(is_basic_int)*/);
440 
441  if (numeric_range_p) {
442  rhs_expr = int_to_expression(FORTRAN_MOD(FORTRAN_DIV(ubval-lbval+incval,
443  incval), rate));
444  }
445  else {
446  rhs_expr = MakeBinaryCall(entity_intrinsic("MOD"),
447  make_ref_expr(nub, NIL),
448  int_to_expression(rate));
449  }
450 
452  make_reference(ib, NIL) ),
454  stmt = make_assign_statement(expr, rhs_expr);
456  CONS(STATEMENT, stmt, NIL ));
457 
458 
459  /* An index LU_IND and a loop for the first iterations are created
460  * to perform the prologue in case the number of iterations is not a
461  * multiple of the unrolling rate:
462  *
463  * DO LU_IND = 0, LU_IB-1, 1
464  * BODY(I\‍(LU_IND*INC + LB))
465  * ENDDO
466  *
467  * FI: Loop Unrolled INDex
468  */
471  copy_basic(indb));
472  AddEntityToCurrentModule(lu_ind);
473 
474  /* Loop range is created */
477  make_ref_expr(ib, NIL),
478  int_to_expression(1) ),
479  int_to_expression(1) );
480  ifdebug(9) {
481  pips_assert("new range is consistent", range_consistent_p(rg));
482  }
483 
484  /* Create body of the loop, with updated index */
488  NIL,
490  body = clone_statement(loop_body(il), cc);
491  free_clone_context(cc);
492 
493  ifdebug(9) {
494  pips_assert("cloned body is consistent", statement_consistent_p(body));
495  /* "gen_copy_tree returns bad statement\n"); */
496  }
497  /* Substitute the initial index by its value in the body */
500  make_ref_expr(lu_ind, NIL),
501  copy_expression(inc)),
502  copy_expression(lb));
503  ifdebug(9) {
504  pips_assert("expr is consistent", expression_consistent_p(expr));
505  /* "gen_copy_tree returns bad expression(s)\n"); */
506  }
507  replace_entity_by_expression(body,ind,expr);
508  free_expression(expr);
509 
510  label_entity = make_new_label(get_current_module_entity());
511  stmt = make_continue_statement(label_entity);
512  body = make_block_statement(
514  );
515  ifdebug(9) {
516  pips_assert("the cloned and substituted body is consistent",
517  statement_consistent_p(body));
518  }
519 
520  /* Create loop and insert it in top block. FI: parallelism could be
521  preserved */
523  make_loop(lu_ind,
524  rg,
525  body,
526  label_entity,
528  UU),
529  NIL));
530 
531  ifdebug(9) {
532  pips_assert("prologue loop inst is consistent",
534  }
535 
537  CONS(STATEMENT,
539  NIL ));
540 
541  /* The unrolled loop is generated:
542  *
543  * DO LU_IND = LU_IB, LU_NUB-1, rate
544  * BODY(I\‍(LU_IND*INC + LB))
545  * BODY(I\‍((LU_IND+1)*INC + LB))
546  * ...
547  * BODY(I\‍((LU_IND+(rate-1))*INC + LB))
548  * ENDDO
549  */
550  /* First, the loop range is generated */
551  rg = make_range(make_ref_expr(ib, NIL),
553  make_ref_expr(nub, NIL),
554  int_to_expression(1) ),
555  int_to_expression(rate) );
556 
557  /* Create body of the loop, with updated index */
559  label_entity = make_new_label(get_current_module_entity());
561  CONS(STATEMENT, make_continue_statement(label_entity), NIL);
562  while(--rate>=0) {
563  /* Last transformated old loop added first */
564  expression tmp_expr;
565  statement transformed_stmt;
566  list body_block = instruction_block(statement_instruction(body));
567 
571  NIL,
573  transformed_stmt = clone_statement(loop_body(il), cc);
574  free_clone_context(cc);
575 
576  ifdebug(9)
577  pips_assert("the cloned body is consistent",
578  statement_consistent_p(transformed_stmt));
580  make_ref_expr(lu_ind, NIL),
581  int_to_expression(rate) );
584  tmp_expr,
585  copy_expression(inc) ),
586  copy_expression(lb) );
587  ifdebug(9) {
588  pips_assert("The expression for the initial index is consistent",
590  }
591  replace_entity_by_expression(transformed_stmt,ind,expr);
592 
593  ifdebug(9) {
594  pips_assert("The new loop body is consistent after index substitution",
595  statement_consistent_p(transformed_stmt));
596  }
597  free_expression(expr);
598 
599  ifdebug(9) {
600  pips_assert("Still true when expr is freed",
601  statement_consistent_p(transformed_stmt));
602  }
603  if(statement_post_processor)
604  statement_post_processor(transformed_stmt);
605 
606 
607  /* Add the transformated old loop body (transformed_stmt) at
608  * the begining of the loop
609  *
610  * For C code, be careful with local declarations and initializations
611  */
612  if( get_bool_property("LOOP_UNROLL_MERGE")
613  && instruction_block_p(statement_instruction(transformed_stmt)) ) {
614  if(ENDP(statement_declarations(body)))
615  statement_declarations(body)=statement_declarations(transformed_stmt);
616  else {
617  list declaration_initializations = NIL;
618  FOREACH(ENTITY,e,statement_declarations(transformed_stmt))
619  {
620  value v = entity_initial(e);
621  if( value_expression_p(v) )
622  {
623  statement s =
626  declaration_initializations =
627  CONS(STATEMENT,s,declaration_initializations);
628  }
629  }
630  declaration_initializations=gen_nreverse(declaration_initializations);
631  instruction_block(statement_instruction(transformed_stmt))=
632  gen_nconc(declaration_initializations,
633  instruction_block(statement_instruction(transformed_stmt)));
634  }
637  instruction_block(statement_instruction(transformed_stmt)));
638  }
639  else {
641  CONS(STATEMENT, transformed_stmt, body_block);
642  }
643  }
644 
645  /* Create loop and insert it in the top block */
646  /* ?? Should execution be the same as initial loop? */
648  make_loop(lu_ind,
649  rg,
650  body,
651  label_entity,
653  UU),
654  NIL));
655 
656  ifdebug(9) {
657  pips_assert("the unrolled loop inst is consistent",
659  }
660 
661 
663  CONS(STATEMENT,
665  NIL ));
666 
667  /* Generate a statement to reinitialize old index
668  * IND = LB + MAX(NUB,0)*INC
669  */
672  make_ref_expr(nub, NIL),
673  int_to_expression(0) ),
674  copy_expression(inc) );
676  copy_expression(lb),
677  expr);
678  expr = make_ref_expr(ind, NIL);
680  rhs_expr );
681  ifdebug(9) {
683  pips_assert("The old index assignment stmt is consistent",
685  }
687  CONS(STATEMENT, stmt, NIL ));
688 
689 
690  /* Free old instruction and replace with block */
691  /* FI: according to me, gen_copy_tree() does not create a copy sharing nothing
692  * with its actual parameter; if the free is executed, Pvecteur normalized_linear
693  * is destroyed (18 January 1993) */
694  /* gen_free(statement_instruction(loop_statement)); */
695  statement_instruction(loop_statement) = block;
696  /* Do not forget to move forbidden information associated with
697  block: */
698  fix_sequence_statement_attributes(loop_statement);
699 
700  ifdebug(9) {
701  print_statement(loop_statement);
702  pips_assert("the unrolled code is consistent",
703  statement_consistent_p(loop_statement));
704  }
705 
706  ifdebug(7) {
707  /* Stop debug in Newgen */
709  }
710 
711  pips_debug(3, "done\n");
712 }
713 
714 void do_loop_unroll(statement loop_statement,
715  int rate,
716  void (*statement_post_processor)(statement))
717 {
718  pips_debug(2, "unroll %d times\n", rate);
719  pips_assert("the statement is a loop",
720  instruction_loop_p(statement_instruction(loop_statement)));
721  pips_assert("the unrolling factor is strictly positive", rate > 0);
722 
723  if(rate>1) {
724  loop il = instruction_loop(statement_instruction(loop_statement));
725  range lr = loop_range(il);
726  expression inc = range_increment(lr);
727  intptr_t incval;
728 
729  // FI: a property should be checked because epilogue cannot be
730  // used if backward compatibility must be maintained
731  if(expression_integer_value(inc, &incval) && incval==1
732  && !get_bool_property("LOOP_UNROLL_WITH_PROLOGUE"))
733  do_loop_unroll_with_epilogue(loop_statement,
734  rate,
735  statement_post_processor);
736  else
737  do_loop_unroll_with_prologue(loop_statement,
738  rate,
739  statement_post_processor);
740  }
741  pips_debug(3, "done\n");
742 }
743 
744 /* fallbacks on do_loop_unroll
745  * without statement post processing
746  */
747 void
748 loop_unroll(statement loop_statement, int rate)
749 {
750  do_loop_unroll(loop_statement, rate, NULL);
751 }
752 
754 {
755  bool unroll_p = false;
756  range lr = loop_range(l);
757  expression lb = range_lower(lr);
758  expression ub = range_upper(lr);
759  expression inc = range_increment(lr);
760  intptr_t lbval, ubval, incval;
761 
762  pips_debug(2, "begin\n");
763 
764  unroll_p = expression_integer_value(lb, &lbval)
765  && expression_integer_value(ub, &ubval)
766  && expression_integer_value(inc, &incval);
767 
768  if(unroll_p) {
769  const char* s = get_string_property("FULL_LOOP_UNROLL_EXCEPTIONS");
770  if(*s!=0) {
772  list exceptions = string_to_user_modules(s);
773  list p = arguments_intersection(callees, exceptions);
774  unroll_p = ENDP(p);
775  gen_free_list(p);
776  }
777  }
778 
779  return unroll_p;
780 }
781 
782 /* get rid of the loop by body replication;
783  *
784  * the loop body is replicated as many times as there are iterations
785  *
786  * FI: could be improved to handle symbolic lower bounds (18 January 1993)
787  */
788 void full_loop_unroll(statement loop_statement)
789 {
790  loop il = instruction_loop(statement_instruction(loop_statement));
791  range lr = loop_range(il);
792  entity ind = loop_index(il);
793  entity flbl = entity_undefined; /* final loop body label */
794  expression lb = range_lower(lr);
795  expression ub = range_upper(lr);
796  expression inc = range_increment(lr);
797  expression rhs_expr, expr;
798  statement stmt;
800  intptr_t lbval, ubval, incval;
801  int iter;
802 
803  pips_debug(2, "begin\n");
804 
805  ifdebug(7) {
806  /* Start debug in Newgen */
808  }
809  /* Validity of transformation should be checked */
810  /* ie.: - pas d'effets de bords dans les expressions duplique'es */
811 
812  if (expression_integer_value(lb, &lbval)
813  && expression_integer_value(ub, &ubval)
814  && expression_integer_value(inc, &incval)) {
815  pips_assert("full_loop_unroll", incval != 0);
816  }
817  else {
818  pips_user_error("loop range for loop %s must be numerically known\n",
820  // previous function is noreturn... but try to please lang.
821  return;
822  }
823 
824  /* Instruction block is created and will contain everything */
826 
827  /* get rid of labels in loop body: don't worry, useful labels have
828  been transformed into arcs by controlizer, you just loose loop
829  labels. However, the label of the last statement in the loop body
830  might be used by an outer loop and, in doubt, should be preserved. */
831 
833 
834  (void) clear_labels (loop_body (il));
835 
836  for(iter = lbval; iter <= ubval; iter += incval) {
837  statement transformed_stmt;
838 
842  NIL,
844  transformed_stmt = clone_statement(loop_body(il), cc);
845  free_clone_context(cc);
846 
847  ifdebug(9)
848  statement_consistent_p(transformed_stmt);
849  expr = int_to_expression(iter);
850  ifdebug(9) {
851  pips_assert("full_loop_unroll", expression_consistent_p(expr));
852  }
853  /* FI: clone_statement() has been used above to perform
854  flatten_code. Hence the declarations are no longer
855  accessible from "transformed_stmt". And when dependent
856  types are used, they are not updated. */
857  replace_entity_by_expression(transformed_stmt,ind,expr);
858  /* Try to update dependent types. Too bad the declarations are
859  scanned again and again. */
862 
863  ifdebug(9) {
864  pips_assert("full_loop_unroll", statement_consistent_p(transformed_stmt));
865  }
866  free_expression(expr);
867 
868  ifdebug(9) {
869  pips_assert("full_loop_unroll", statement_consistent_p(transformed_stmt));
870  }
871 
872  /* Add the transformated old loop body (transformed_stmt) at
873  * the end of the loop */
874  if( statement_block_p(transformed_stmt) && get_bool_property("LOOP_UNROLL_MERGE"))
875  {
876  if(ENDP(statement_declarations(loop_statement)))
877  statement_declarations(loop_statement)=statement_declarations(transformed_stmt);
878  else {
879  list declaration_initializations = NIL;
880  FOREACH(ENTITY,e,statement_declarations(transformed_stmt))
881  {
882  value v = entity_initial(e);
883  if( value_expression_p(v) )
884  {
888  declaration_initializations=CONS(STATEMENT,s,declaration_initializations);
889  }
890  }
891  declaration_initializations=gen_nreverse(declaration_initializations);
892  instruction_block(statement_instruction(transformed_stmt))=
893  gen_nconc(declaration_initializations,instruction_block(statement_instruction(transformed_stmt)));
894  }
897  instruction_block(statement_instruction(transformed_stmt)));
898  }
899  else {
902  CONS(STATEMENT, transformed_stmt, NIL));
903  }
904  }
905 
906  /* Generate a CONTINUE to carry the final loop body label in case an
907  outer loop uses it */
908  if(!entity_empty_label_p(flbl)) {
910  ifdebug(9) {
912  pips_assert("full_loop_unroll", statement_consistent_p(stmt));
913  }
915  CONS(STATEMENT, stmt, NIL ));
916  }
917 
918  /* Generate a statement to reinitialize old index */
919  /* SG: only needed if index is not private */
920  if(entity_in_list_p(ind,loop_locals(il))) {
921  rhs_expr = int_to_expression(iter);
922  expr = make_ref_expr(ind, NIL);
923  stmt = make_assign_statement(expr, rhs_expr);
924  ifdebug(9) {
926  pips_assert("full_loop_unroll", statement_consistent_p(stmt));
927  }
929  CONS(STATEMENT, stmt, NIL ));
930  }
931 
932 
933  /* Free old instruction and replace with block */
934  /* FI: according to me, gen_copy_tree() does not create a copy sharing nothing
935  * with its actual parameter; if the free is executed, Pvecteur normalized_linear
936  * is destroyed (18 January 1993) */
937  free_instruction(statement_instruction(loop_statement));
938  statement_instruction(loop_statement) = block;
939  /* Do not forget to move forbidden information associated with
940  block: */
941  fix_sequence_statement_attributes(loop_statement);
942  clean_up_sequences(loop_statement);
943 
944  ifdebug(9) {
945  print_statement(loop_statement);
946  pips_assert("full_loop_unroll", statement_consistent_p(loop_statement));
947  }
948  /* ?? Bad condition */
949  if(get_debug_level()==7) {
950  /* Stop debug in Newgen */
952  }
953 
954  pips_debug(3, "done\n");
955 }
956 
957 /* Top-level functions
958  */
959 
960 bool unroll(const string mod_name)
961 {
962  statement mod_stmt;
963  const char *lp_label = NULL;
964  entity lb_ent;
965  int rate;
966  bool return_status =true;
967 
968  debug_on("UNROLL_DEBUG_LEVEL");
969 
970  /* Get the loop label form the user */
971  lp_label=get_string_property_or_ask("LOOP_LABEL","Which loop do you want to unroll?\n(give its label):");
972  if( empty_string_p(lp_label) )
973  return_status = false;
974  else {
975  lb_ent = find_label_entity(mod_name, lp_label);
976  if (entity_undefined_p(lb_ent))
977  user_error("unroll", "loop label `%s' does not exist\n", lp_label);
978 
979  /* Get the unrolling factor from the user */
980  rate = get_int_property("UNROLL_RATE");
981  if( rate <= 1 ) {
982  string resp = user_request("How many times do you want to unroll?\n(choose integer greater or egal to 2): ");
983 
984  if (empty_string_p(resp))
985  /* User asked to cancel: */
986  return_status = false;
987  else {
988  if(sscanf(resp, "%d", &rate)!=1 || rate <= 1)
989  user_error("unroll", "unroll factor should be greater than 2\n");
990  }
991  }
992  if( return_status ) {
993 
994  pips_debug(1,"Unroll %d times loop %s in module %s\n",
995  rate, lp_label, mod_name);
996 
997  /* Sets the current module to "mod_name". */
998  /* current_module(module_name_to_entity(mod_name)); */
999 
1000  /* DBR_CODE will be changed: argument "pure" should take false
1001  but this would be useless
1002  since there is only *one* version of code; a new version
1003  will be put back in the
1004  data base after unrolling */
1005 
1006  mod_stmt = (statement) db_get_memory_resource(DBR_CODE, mod_name, true);
1007 
1008  /* prelude */
1010  set_current_module_statement( mod_stmt);
1011 
1012  statement loop_statement = find_loop_from_label(mod_stmt,lb_ent);
1013  if( ! statement_undefined_p(loop_statement) ) {
1014  instruction i = statement_instruction(loop_statement);
1015  loop l = instruction_loop(i);
1016  /* Validity of transformation should be checked */
1017  /* ie.: - no side effects in replicated expressions */
1018  /* No dependent types in C */
1020  bool dependent_p = false;
1021  FOREACH(ENTITY, v, vl) {
1022  type t = entity_type(v);
1023  if(dependent_type_p(t)) {
1024  dependent_p = true;
1025  break;
1026  }
1027  }
1028 
1029  if(dependent_p) {
1030  pips_user_warning("Loop cannot be unrolled because it contains a dependent type.\n");
1031  return_status = false;
1032  }
1033  else {
1034  /* do the job */
1035  loop_unroll(loop_statement,rate);
1036  }
1037  }
1038  else
1039  pips_user_error("label '%s' is not linked to a loop\n", lp_label);
1040 
1041  if(return_status) {
1042  /* Reorder the module, because new statements have been generated. */
1043  module_reorder(mod_stmt);
1044 
1045  DB_PUT_MEMORY_RESOURCE(DBR_CODE, mod_name, mod_stmt);
1046  }
1047  /*postlude*/
1050  return_status = true;
1051  }
1052  }
1053 
1054  pips_debug(2, "done for %s\n", mod_name);
1055  debug_off();
1056 
1057  if ( ! return_status )
1058  user_log("Loop unrolling has been cancelled.\n");
1059 
1060  return return_status;
1061 }
1062 
1063 static
1065 {
1067  bool go_on = true;
1068 
1069  if(instruction_loop_p(inst)) {
1070  full_loop_unroll(s);
1071  }
1072 
1073  return go_on;
1074 }
1075 
1076 
1077 bool full_unroll(const string mod_name)
1078 {
1079  statement mod_stmt = statement_undefined;
1080  const char *lp_label = string_undefined;
1081  entity lb_ent = entity_undefined;
1082  bool return_status = true;
1083 
1084  debug_on("FULL_UNROLL_DEBUG_LEVEL");
1085 
1086  /* user interaction */
1087  lp_label = get_string_property_or_ask("LOOP_LABEL","loop to fully unroll ?");
1088  if( empty_string_p(lp_label) )
1089  return_status = false;
1090  else {
1091  lb_ent = find_label_entity(mod_name,lp_label);
1092  if( entity_undefined_p(lb_ent) )
1093  pips_user_warning("loop label `%s' does not exist, unrolling all loops\n", lp_label);
1094  mod_stmt = (statement) db_get_memory_resource(DBR_CODE, mod_name, true);
1095 
1096  /* prelude */
1098  set_current_module_statement( mod_stmt);
1099 
1100  /* do the job */
1101  if(entity_undefined_p(lb_ent)) {
1102  gen_recurse (mod_stmt, statement_domain,
1103  (bool(*)(void*))apply_full_loop_unroll, gen_null);
1104  }
1105  else {
1106  statement loop_statement = find_loop_from_label(mod_stmt,lb_ent);
1107  if( statement_undefined_p(loop_statement) )
1108  pips_user_error("label '%s' is not put on a loop\n",lp_label);
1109  else
1110  full_loop_unroll(loop_statement);
1111  }
1112 
1113  /* Reorder the module, because new statements have been generated. */
1114  module_reorder(mod_stmt);
1115 
1116  DB_PUT_MEMORY_RESOURCE(DBR_CODE, mod_name, mod_stmt);
1117  /*postlude*/
1120  }
1121  if( !return_status)
1122  user_log("transformation has been cancelled\n");
1123  pips_debug(2,"done for %s\n", mod_name);
1124  debug_off();
1125  /* Reorder the module, because new statements have been generated. */
1126  module_reorder(mod_stmt);
1127 
1128  return return_status;
1129 }
1130 
1131 
1132 ␌
1135 
1136 /* C must be a capital C... This should be improved with
1137  regular expressions, with a property to set the pragma or comment...
1138 
1139  This algorithm is more efficient if we have far more loops than
1140  comments... :-)
1141 
1142  Furthermore, people want to unroll only loops that are designated or
1143  all loops but those that are designated.
1144 
1145  Loops can be tagged by the loop index, the loop label or a pragma.
1146 
1147  A lot of improvement ahead before we can think of matching TSF
1148  flexibility... */
1149 #define FULL_UNROLL_PRAGMA "Cxxx"
1150 
1152 {
1154 
1156  && strstr(statement_comments(s), FULL_UNROLL_PRAGMA)!=NULL) {
1158  if(instruction_loop_p(inst)) {
1159  /* full_loop_unroll() does not work all the time! */
1160  full_loop_unroll(s);
1162  }
1163  else {
1164  /* The full unroll pragma must comment a DO instruction */
1165  pips_user_warning("Unroll pragma should decorate a loop...\n");
1166  }
1167  }
1168 }
1169 
1170 bool full_unroll_pragma(const string mod_name)
1171 {
1173  set_current_module_statement( (statement) db_get_memory_resource(DBR_CODE, mod_name, true) );
1174 
1175  statement mod_stmt = statement_undefined;
1176  bool return_status = false;
1177 
1178  debug_on("FULL_UNROLL_DEBUG_LEVEL");
1179 
1180  debug(1,"full_unroll_pragma","Fully unroll loops with pragma in module %s\n",
1181  mod_name);
1182 
1183  /* Keep track of effects on code */
1186 
1187  /* Perform the loop unrollings */
1188  mod_stmt = (statement) db_get_memory_resource(DBR_CODE, mod_name, true);
1189 
1190  // gen_recurse (mod_stmt, statement_domain,
1191  // find_unroll_pragma_and_fully_unroll, gen_null);
1192 
1193  /* Perform the transformation bottom up to reduce the scanning and the
1194  number of unrollings */
1195  gen_recurse (mod_stmt, statement_domain,
1197 
1198  /* Reorder the module, because new statements have been generated. */
1199  module_reorder(mod_stmt);
1200 
1201  DB_PUT_MEMORY_RESOURCE(DBR_CODE, mod_name, mod_stmt);
1202 
1203  /* Provide statistics about changes performed */
1205  user_log("%d loop%s unrolled as requested\n", number_of_unrolled_loops,
1206  number_of_unrolled_loops>1?"s":"");
1207  return_status = true;
1208  }
1209  else {
1211  user_log("%d loop%s unrolled as requested\n", number_of_unrolled_loops,
1212  number_of_unrolled_loops>1?"s":"");
1213  user_log("%d loop%s could not be unrolled as requested\n", failures,
1214  failures>1?"s":"");
1215  return_status = false;
1216  }
1217 
1218  debug(1,"full_unroll_pragma","done for %s\n", mod_name);
1219  debug_off();
1220 
1223 
1224  return return_status;
1225 }
int get_int_property(const string)
void user_log(const char *format,...)
Definition: message.c:234
clone_context make_clone_context(entity a1, entity a2, list a3, statement a4)
Definition: cloning.c:52
void free_clone_context(clone_context p)
Definition: cloning.c:19
bool instruction_consistent_p(instruction p)
Definition: ri.c:1124
execution make_execution(enum execution_utype tag, void *val)
Definition: ri.c:838
expression make_expression(syntax a1, normalized a2)
Definition: ri.c:886
loop make_loop(entity a1, range a2, statement a3, entity a4, execution a5, list a6)
Definition: ri.c:1301
basic copy_basic(basic p)
BASIC.
Definition: ri.c:104
expression copy_expression(expression p)
EXPRESSION.
Definition: ri.c:850
reference make_reference(entity a1, list a2)
Definition: ri.c:2083
bool statement_consistent_p(statement p)
Definition: ri.c:2195
bool range_consistent_p(range p)
Definition: ri.c:2014
bool expression_consistent_p(expression p)
Definition: ri.c:859
void free_expression(expression p)
Definition: ri.c:853
void free_instruction(instruction p)
Definition: ri.c:1118
instruction make_instruction(enum instruction_utype tag, void *val)
Definition: ri.c:1166
syntax make_syntax(enum syntax_utype tag, void *val)
Definition: ri.c:2491
execution copy_execution(execution p)
EXECUTION.
Definition: ri.c:795
range make_range(expression a1, expression a2, expression a3)
Definition: ri.c:2041
static int count
Definition: SDG.c:519
list arguments_intersection(list a1, list a2)
Build a new list with all entities occuring in both a1 and a2.
Definition: arguments.c:158
bool clean_up_sequences(statement s)
Recursively clean up the statement sequences by fusing them if possible and by removing useless one.
statement clone_statement(statement s, clone_context cc)
clone_statement.c
struct _newgen_struct_statement_ * statement
Definition: cloning.h:21
bool empty_string_p(const char *s)
Definition: entity_names.c:239
char * get_string_property(const char *)
bool get_bool_property(const string)
FC 2015-07-20: yuk, moved out to prevent an include cycle dependency include "properties....
int gen_debug
Function interface for user applications.
Definition: genClib.c:69
#define GEN_DBG_CHECK
Definition: genC.h:200
#define gen_recurse(start, domain_number, flt, rwt)
Definition: genC.h:283
statement make_block_statement(list)
Make a block statement from a list of statement.
Definition: statement.c:616
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
void reset_current_module_entity(void)
Reset the current module entity.
Definition: static.c:97
void reset_current_module_statement(void)
Reset the current module statement.
Definition: static.c:221
statement set_current_module_statement(statement)
Set the current module statement.
Definition: static.c:165
statement get_current_module_statement(void)
Get the current module statement.
Definition: static.c:208
entity set_current_module_entity(entity)
static.c
Definition: static.c:66
entity get_current_module_entity(void)
Get the entity of the current module.
Definition: static.c:85
void replace_entity_by_expression(void *s, entity ent, expression exp)
replace all reference to entity ent by expression exp in s.
Definition: replace.c:220
void gen_null(__attribute__((unused)) void *unused)
Ignore the argument.
Definition: genClib.c:2752
bool gen_true(__attribute__((unused)) gen_chunk *unused)
Return true and ignore the argument.
Definition: genClib.c:2780
instruction make_instruction_block(list statements)
Build an instruction block from a list of statements.
Definition: instruction.c:106
statement make_new_loop_statement(entity i, expression low, expression up, expression inc, statement b, execution e)
This is an ad'hoc function designed for do_loop_unroll_with_epilogue().
Definition: loop.c:839
#define ENDP(l)
Test if a list is empty.
Definition: newgen_list.h:66
list gen_nreverse(list cp)
reverse a list in place
Definition: list.c:304
#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
list gen_nconc(list cp1, list cp2)
physically concatenates CP1 and CP2 but do not duplicates the elements
Definition: list.c:344
void gen_free_list(list l)
free the spine of the list
Definition: list.c:327
#define FOREACH(_fe_CASTER, _fe_item, _fe_list)
Apply/map an instruction block on all the elements of a list.
Definition: newgen_list.h:179
string db_get_memory_resource(const char *rname, const char *oname, bool pure)
Return the pointer to the resource, whatever it is.
Definition: database.c:755
#define DB_PUT_MEMORY_RESOURCE(res_name, own_name, res_val)
conform to old interface.
Definition: pipsdbm-local.h:66
statement make_assign_statement(expression, expression)
Definition: statement.c:583
list statement_to_called_user_entities(statement)
Get a list of all user function called recursively within a statement:
Definition: statement.c:3478
statement make_continue_statement(entity)
Definition: statement.c:953
statement clear_labels(statement)
Get rid of all labels in controlized code before duplication.
Definition: statement.c:1560
bool empty_comments_p(const char *)
Definition: statement.c:107
void fix_sequence_statement_attributes(statement)
Since blocks are not represented in Fortran, they cannot carry a label.
Definition: statement.c:2016
entity find_final_statement_label(statement)
Find the label associated with the last statement executed within s.
Definition: statement.c:4360
static void find_unroll_pragma_and_fully_unroll(statement s)
Definition: loop_unroll.c:1151
static bool apply_full_loop_unroll(struct _newgen_struct_statement_ *s)
Definition: loop_unroll.c:1064
bool loop_fully_unrollable_p(loop l)
Definition: loop_unroll.c:753
#define INDEX_NAME
Definition: loop_unroll.c:56
#define INTERMEDIATE_BOUND_NAME
Definition: loop_unroll.c:55
#define FULL_UNROLL_PRAGMA
C must be a capital C...
Definition: loop_unroll.c:1149
static int number_of_requested_unrollings
Definition: loop_unroll.c:1134
bool full_unroll_pragma(const string mod_name)
Definition: loop_unroll.c:1170
void loop_unroll(statement loop_statement, int rate)
fallbacks on do_loop_unroll without statement post processing
Definition: loop_unroll.c:748
static basic basic_int_to_signed_basic(basic b)
Definition: loop_unroll.c:58
static void do_loop_unroll_with_epilogue(statement loop_statement, int rate, void(*statement_post_processor)(statement))
db_get_current_module_name() unusable because module not set, and setting it causes previous current ...
Definition: loop_unroll.c:95
#define NORMALIZED_UPPER_BOUND_NAME
Definition: loop_unroll.c:54
bool unroll(const string mod_name)
Top-level functions.
Definition: loop_unroll.c:960
static void do_loop_unroll_with_prologue(statement loop_statement, int rate, void(*statement_post_processor)(statement))
This function unrolls any DO loop by a constant factor "rate".
Definition: loop_unroll.c:341
static int number_of_unrolled_loops
Definition: loop_unroll.c:1133
bool full_unroll(const string mod_name)
Definition: loop_unroll.c:1077
void full_loop_unroll(statement loop_statement)
get rid of the loop by body replication;
Definition: loop_unroll.c:788
void do_loop_unroll(statement loop_statement, int rate, void(*statement_post_processor)(statement))
loop_unroll.c
Definition: loop_unroll.c:714
#define debug_on(env)
Definition: misc-local.h:157
#define pips_debug
these macros use the GNU extensions that allow variadic macros, including with an empty list.
Definition: misc-local.h:145
#define pips_user_warning
Definition: misc-local.h:146
#define FORTRAN_DIV(n, d)
Definition: misc-local.h:213
#define FORTRAN_MOD(n, m)
Definition: misc-local.h:215
#define pips_assert(what, predicate)
common macros, two flavors depending on NDEBUG
Definition: misc-local.h:172
#define debug_off()
Definition: misc-local.h:160
#define user_error(fn,...)
Definition: misc-local.h:265
#define pips_user_error
Definition: misc-local.h:147
int get_debug_level(void)
GET_DEBUG_LEVEL returns the current debugging level.
Definition: debug.c:67
void debug(const int the_expected_debug_level, const char *calling_function_name, const char *a_message_format,...)
ARARGS0.
Definition: debug.c:189
string user_request(const char *,...)
#define string_undefined
Definition: newgen_types.h:40
#define UU
Definition: newgen_types.h:98
void print_statement(statement)
Print a statement on stderr.
Definition: statement.c:98
const char * get_string_property_or_ask(const char *, const char[])
bool module_reorder(statement body)
Reorder a module and recompute order to statement if any.
Definition: reorder.c:244
#define instruction_block_p(i)
#define MINUS_OPERATOR_NAME
#define PLUS_OPERATOR_NAME
#define statement_block_p(stat)
#define MAX0_OPERATOR_NAME
#define DIVIDE_OPERATOR_NAME
#define instruction_block(i)
#define make_statement_list(stats...)
easy list constructor
#define MULTIPLY_OPERATOR_NAME
bool entity_in_list_p(entity ent, list ent_l)
look for ent in ent_l
Definition: entity.c:2221
entity module_name_to_entity(const char *mn)
This is an alias for local_name_to_top_level_entity.
Definition: entity.c:1479
entity entity_empty_label(void)
Definition: entity.c:1105
bool entity_empty_label_p(entity e)
Definition: entity.c:666
entity make_new_label(entity module)
This function returns a new label.
Definition: entity.c:357
entity entity_intrinsic(const char *name)
FI: I do not understand this function name (see next one!).
Definition: entity.c:1292
const char * label_local_name(entity e)
END_EOLE.
Definition: entity.c:604
bool expression_integer_value(expression e, intptr_t *pval)
Definition: eval.c:792
expression entity_to_expression(entity e)
if v is a constant, returns a constant call.
Definition: expression.c:165
expression MakeBinaryCall(entity f, expression eg, expression ed)
Creates a call expression to a function with 2 arguments.
Definition: expression.c:354
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 make_ref_expr(entity ent, list args)
Definition: expression.c:4316
list string_to_user_modules(const char *s)
Build a list of functions from a string s containing SPACE separated function names.
Definition: module.c:562
type ultimate_type(type)
Definition: type.c:3466
bool dependent_type_p(type)
A type is dependent in many ways according to definitions given in Wikipedia.
Definition: type.c:5849
void AddEntityToCurrentModule(entity)
Add a variable entity to the current module declarations.
Definition: variable.c:260
entity make_new_scalar_variable_with_prefix(const char *, entity, basic)
Create a new scalar variable of type b in the given module.
Definition: variable.c:592
entity find_label_entity(const char *, const char *)
util.c
Definition: util.c:43
#define loop_body(x)
Definition: ri.h:1644
#define normalized_undefined
Definition: ri.h:1745
#define loop_execution(x)
Definition: ri.h:1648
#define basic_int_p(x)
Definition: ri.h:614
#define instruction_loop_p(x)
Definition: ri.h:1518
#define basic_int(x)
Definition: ri.h:616
#define range_upper(x)
Definition: ri.h:2290
#define ENTITY(x)
ENTITY.
Definition: ri.h:2755
#define instruction_loop(x)
Definition: ri.h:1520
#define range_undefined
Definition: ri.h:2263
#define type_variable(x)
Definition: ri.h:2949
#define statement_domain
newgen_sizeofexpression_domain_defined
Definition: ri.h:362
@ is_syntax_reference
Definition: ri.h:2691
#define range_increment(x)
Definition: ri.h:2292
#define statement_label(x)
Definition: ri.h:2450
#define entity_undefined_p(x)
Definition: ri.h:2762
#define entity_undefined
Definition: ri.h:2761
@ is_instruction_loop
Definition: ri.h:1471
#define loop_label(x)
Definition: ri.h:1646
#define loop_locals(x)
Definition: ri.h:1650
#define range_lower(x)
Definition: ri.h:2288
#define statement_declarations(x)
Definition: ri.h:2460
#define statement_instruction(x)
Definition: ri.h:2458
#define statement_comments(x)
Definition: ri.h:2456
#define loop_range(x)
Definition: ri.h:1642
@ is_execution_sequential
Definition: ri.h:1189
#define statement_undefined_p(x)
Definition: ri.h:2420
#define entity_type(x)
Definition: ri.h:2792
#define value_expression_p(x)
Definition: ri.h:3080
#define value_expression(x)
Definition: ri.h:3082
#define loop_index(x)
Definition: ri.h:1640
#define variable_basic(x)
Definition: ri.h:3120
#define statement_undefined
Definition: ri.h:2419
#define STATEMENT(x)
STATEMENT.
Definition: ri.h:2413
#define entity_initial(x)
Definition: ri.h:2796
#define ifdebug(n)
Definition: sg.c:47
#define intptr_t
Definition: stdint.in.h:294
The structure used to build lists in NewGen.
Definition: newgen_list.h:41
Definition: statement.c:54
struct block block
statement find_loop_from_label(statement, entity)
Definition: util.c:218